dotemacs

My Emacs configuration
git clone git://git.entf.net/dotemacs
Log | Files | Refs | LICENSE

slynk.lisp (160408B)


      1 ;;;; slynk.lisp --- Server for SLY commands.
      2 ;;;
      3 ;;; This code has been placed in the Public Domain.  All warranties
      4 ;;; are disclaimed.
      5 ;;;
      6 ;;; This file defines the "Slynk" TCP server for Emacs to talk to. The
      7 ;;; code in this file is purely portable Common Lisp. We do require a
      8 ;;; smattering of non-portable functions in order to write the server,
      9 ;;; so we have defined them in `slynk-backend.lisp' and implemented
     10 ;;; them separately for each Lisp implementation. These extensions are
     11 ;;; available to us here via the `SLYNK-BACKEND' package.
     12 
     13 (defpackage :slynk
     14   (:use :cl :slynk-backend :slynk-match :slynk-rpc)
     15   (:export #:startup-multiprocessing
     16            #:start-server
     17            #:create-server
     18            #:stop-server
     19            #:restart-server
     20            #:ed-in-emacs
     21            #:inspect-in-emacs
     22            #:print-indentation-lossage
     23            #:invoke-sly-debugger
     24            #:slynk-debugger-hook
     25            #:emacs-inspect
     26            ;;#:inspect-slot-for-emacs
     27            #:authenticate-client
     28            #:*loopback-interface*
     29            #:*buffer-readtable*
     30            #:process-requests)
     31   ;; These are user-configurable variables:
     32   (:export #:*communication-style*
     33            #:*dont-close*
     34            #:*fasl-pathname-function*
     35            #:*log-events*
     36            #:*log-output*
     37            #:*configure-emacs-indentation*
     38            #:*readtable-alist*
     39            #:*global-debugger*
     40            #:*sly-db-quit-restart*
     41            #:*backtrace-printer-bindings*
     42            #:*default-worker-thread-bindings*
     43            #:*macroexpand-printer-bindings*
     44            #:*slynk-pprint-bindings*
     45            #:*string-elision-length*
     46            #:*inspector-verbose*
     47            #:*require-module*
     48            #:*eval-for-emacs-wrappers*
     49            #:*debugger-extra-options*
     50            ;; These are exceptions: they are defined later in
     51            ;; slynk-mrepl.lisp
     52            ;;
     53            #:*globally-redirect-io*
     54            #:*use-dedicated-output-stream*
     55            #:*dedicated-output-stream-port*
     56            #:*dedicated-output-stream-buffering*
     57            ;; This is SETFable.
     58            #:debug-on-slynk-error
     59            ;; These are re-exported directly from the backend:
     60            #:buffer-first-change
     61            #:frame-source-location
     62            #:gdb-initial-commands
     63            #:restart-frame
     64            #:sly-db-step
     65            #:sly-db-break
     66            #:sly-db-break-on-return
     67            #:default-directory
     68            #:set-default-directory
     69            #:quit-lisp
     70            #:eval-for-emacs
     71            #:eval-in-emacs
     72            #:y-or-n-p-in-emacs
     73            #:*find-definitions-right-trim*
     74            #:*find-definitions-left-trim*
     75            #:*after-toggle-trace-hook*
     76            #:*echo-number-alist*
     77            #:*present-number-alist*))
     78 
     79 (in-package :slynk)
     80 
     81 
     82 ;;;; Top-level variables, constants, macros
     83 
     84 (defconstant cl-package (find-package :cl)
     85   "The COMMON-LISP package.")
     86 
     87 (defconstant +keyword-package+ (find-package :keyword)
     88   "The KEYWORD package.")
     89 
     90 (defconstant default-server-port 4005
     91   "The default TCP port for the server (when started manually).")
     92 
     93 (defvar *slynk-debug-p* t
     94   "When true, print extra debugging information.")
     95 
     96 (defvar *m-x-sly-from-emacs* nil
     97   "Bound to non-nil in START-SERVER.")
     98 
     99 (defvar *backtrace-pprint-dispatch-table*
    100   (let ((table (copy-pprint-dispatch nil)))
    101     (flet ((print-string (stream string)
    102              (cond (*print-escape*
    103                     (escape-string string stream
    104                                    :map '((#\" . "\\\"")
    105                                           (#\\ . "\\\\")
    106                                           (#\newline . "\\n")
    107                                           (#\return . "\\r"))))
    108                    (t (write-string string stream)))))
    109       (set-pprint-dispatch 'string  #'print-string 0 table)
    110       table)))
    111 
    112 (defvar *backtrace-printer-bindings*
    113   `((*print-pretty*           . t)
    114     (*print-readably*         . nil)
    115     (*print-level*            . 4)
    116     (*print-length*           . 6)
    117     (*print-lines*            . 1)
    118     (*print-right-margin*     . 200)
    119     (*print-pprint-dispatch*  . ,*backtrace-pprint-dispatch-table*))
    120   "Pretter settings for printing backtraces.")
    121 
    122 (defvar *default-worker-thread-bindings* '()
    123   "An alist to initialize dynamic variables in worker threads.
    124 The list has the form ((VAR . VALUE) ...).  Each variable VAR will be
    125 bound to the corresponding VALUE.")
    126 
    127 (defun call-with-bindings (alist fun)
    128   "Call FUN with variables bound according to ALIST.
    129 ALIST is a list of the form ((VAR . VAL) ...)."
    130   (if (null alist)
    131       (funcall fun)
    132       (let* ((rlist (reverse alist))
    133              (vars (mapcar #'car rlist))
    134              (vals (mapcar #'cdr rlist)))
    135         (progv vars vals
    136           (funcall fun)))))
    137 
    138 (defmacro with-bindings (alist &body body)
    139   "See `call-with-bindings'.
    140 Bindings appearing earlier in the list take priority"
    141   `(call-with-bindings ,alist (lambda () ,@body)))
    142 
    143 ;;; The `DEFSLYFUN' macro defines a function that Emacs can call via
    144 ;;; RPC.
    145 
    146 (defvar *slyfuns* (make-hash-table)
    147   "A map of Sly functions.")
    148 
    149 (defmacro defslyfun (name arglist &body rest)
    150   "A DEFUN for functions that Emacs can call by RPC."
    151   `(progn
    152      (defun ,name ,arglist ,@rest)
    153      (setf (gethash ',name *slyfuns*) #',name)
    154      ;; see <http://www.franz.com/support/documentation/6.2/\
    155      ;; doc/pages/variables/compiler/\
    156      ;; s_cltl1-compile-file-toplevel-compatibility-p_s.htm>
    157      (eval-when (:compile-toplevel :load-toplevel :execute)
    158        (export ',name (symbol-package ',name)))))
    159 
    160 (defun missing-arg ()
    161   "A function that the compiler knows will never to return a value.
    162 You can use (MISSING-ARG) as the initform for defstruct slots that
    163 must always be supplied. This way the :TYPE slot option need not
    164 include some arbitrary initial value like NIL."
    165   (error "A required &KEY or &OPTIONAL argument was not supplied."))
    166 
    167 
    168 ;;;; Hooks
    169 ;;;
    170 ;;; We use Emacs-like `add-hook' and `run-hook' utilities to support
    171 ;;; simple indirection. The interface is more CLish than the Emacs
    172 ;;; Lisp one.
    173 
    174 (defmacro add-hook (place function)
    175   "Add FUNCTION to the list of values on PLACE."
    176   `(pushnew ,function ,place))
    177 
    178 (defun run-hook (functions &rest arguments)
    179   "Call each of FUNCTIONS with ARGUMENTS."
    180   (dolist (function functions)
    181     (apply function arguments)))
    182 
    183 (defvar *new-connection-hook* '()
    184   "This hook is run each time a connection is established.
    185 The connection structure is given as the argument.
    186 Backend code should treat the connection structure as opaque.")
    187 
    188 (defvar *connection-closed-hook* '()
    189   "This hook is run when a connection is closed.
    190 The connection as passed as an argument.
    191 Backend code should treat the connection structure as opaque.")
    192 
    193 (defvar *pre-reply-hook* '()
    194   "Hook run (without arguments) immediately before replying to an RPC.")
    195 
    196 (defvar *after-init-hook* '()
    197   "Hook run after user init files are loaded.")
    198 
    199 
    200 ;;;; Connections
    201 ;;;
    202 ;;; Connection structures represent the network connections between
    203 ;;; Emacs and Lisp. 
    204 ;;;
    205 (defstruct (connection
    206              (:constructor %make-connection)
    207              (:conc-name connection-)
    208              (:print-function print-connection))
    209   ;; The listening socket. (usually closed)
    210   ;; 
    211   (socket           (missing-arg) :type t :read-only t)
    212   ;; Character I/O stream of socket connection.  Read-only to avoid
    213   ;; race conditions during initialization.
    214   ;; 
    215   (socket-io        (missing-arg) :type stream :read-only t)
    216   ;; An alist of (ID . CHANNEL) entries. Channels are good for
    217   ;; streaming data over the wire (see their description in sly.el)
    218   ;;
    219   (channel-counter 0 :type number)
    220   (channels '() :type list)
    221   ;; A list of LISTENER objects. Each listener has a couple of streams
    222   ;; and an environment (an alist of bindings)
    223   ;;
    224   (listeners '() :type list)
    225   ;; A list of INSPECTOR objects. Each inspector has its own history
    226   ;; of inspected objects. An inspector might also be tied to a
    227   ;; specific thread.
    228   ;; 
    229   (inspectors '() :type list)
    230   ;;Cache of macro-indentation information that
    231   ;; has been sent to Emacs.  This is used for preparing deltas to
    232   ;; update Emacs's knowledge.  Maps: symbol ->
    233   ;; indentation-specification
    234   ;; 
    235   (indentation-cache (make-hash-table :test 'eq) :type hash-table)
    236   ;; The list of packages represented in the cache:
    237   ;; 
    238   (indentation-cache-packages '())
    239   ;; The communication style used.
    240   ;; 
    241   (communication-style nil :type (member nil :spawn :sigio :fd-handler))
    242   )
    243 
    244 (defun print-connection (conn stream depth)
    245   (declare (ignore depth))
    246   (print-unreadable-object (conn stream :type t :identity t)))
    247 
    248 (defstruct (singlethreaded-connection (:include connection)
    249                                       (:conc-name sconn.))
    250   ;; The SIGINT handler we should restore when the connection is
    251   ;; closed.
    252   saved-sigint-handler
    253   ;; A queue of events.  Not all events can be processed in order and
    254   ;; we need a place to stored them.
    255   (event-queue '() :type list)
    256   ;; A counter that is incremented whenever an event is added to the
    257   ;; queue.  This is used to detected modifications to the event queue
    258   ;; by interrupts.  The counter wraps around.
    259   (events-enqueued 0 :type fixnum))
    260 
    261 (defstruct (multithreaded-connection (:include connection)
    262                                      (:conc-name mconn.))
    263   ;; In multithreaded systems we delegate certain tasks to specific
    264   ;; threads. The `reader-thread' is responsible for reading network
    265   ;; requests from Emacs and sending them to the `control-thread'; the
    266   ;; `control-thread' is responsible for dispatching requests to the
    267   ;; threads that should handle them.
    268   reader-thread
    269   control-thread
    270   auto-flush-thread
    271   indentation-cache-thread
    272   ;; List of threads that are currently processing requests.  We use
    273   ;; this to find the newest/current thread for an interrupt.  In the
    274   ;; future we may store here (thread . request-tag) pairs so that we
    275   ;; can interrupt specific requests.
    276   (active-threads '() :type list)
    277   )
    278 
    279 (defvar *emacs-connection* nil
    280   "The connection to Emacs currently in use.")
    281 
    282 (defun make-connection (socket stream style)
    283   (let ((conn (funcall (ecase style
    284                          (:spawn
    285                           #'make-multithreaded-connection)
    286                          ((:sigio nil :fd-handler)
    287                           #'make-singlethreaded-connection))
    288                        :socket socket
    289                        :socket-io stream
    290                        :communication-style style)))
    291     (run-hook *new-connection-hook* conn)
    292     (send-to-sentinel `(:add-connection ,conn))
    293     conn))
    294 
    295 (defslyfun ping (tag)
    296   tag)
    297 
    298 (defun safe-backtrace ()
    299   (ignore-errors
    300     (call-with-debugging-environment
    301      (lambda () (backtrace 0 nil)))))
    302 
    303 (define-condition slynk-error (error)
    304   ((backtrace :initarg :backtrace :reader slynk-error.backtrace)
    305    (condition :initarg :condition :reader slynk-error.condition))
    306   (:report (lambda (c s) (princ (slynk-error.condition c) s)))
    307   (:documentation "Condition which carries a backtrace."))
    308 
    309 (defun signal-slynk-error (condition &optional (backtrace (safe-backtrace)))
    310   (error 'slynk-error :condition condition :backtrace backtrace))
    311 
    312 (defvar *debug-on-slynk-protocol-error* nil
    313   "When non-nil invoke the system debugger on errors that were
    314 signalled during decoding/encoding the wire protocol.  Do not set this
    315 to T unless you want to debug slynk internals.")
    316 
    317 (defmacro with-slynk-error-handler ((connection) &body body)
    318   "Close the connection on internal `slynk-error's."
    319   (let ((conn (gensym)))
    320   `(let ((,conn ,connection))
    321      (handler-case
    322          (handler-bind ((slynk-error
    323                          (lambda (condition)
    324                            (when *debug-on-slynk-protocol-error*
    325                              (invoke-default-debugger condition)))))
    326            (progn . ,body))
    327        (slynk-error (condition)
    328          (close-connection ,conn
    329                            (slynk-error.condition condition)
    330                            (slynk-error.backtrace condition)))))))
    331 
    332 (defmacro with-panic-handler ((connection) &body body)
    333   "Close the connection on unhandled `serious-condition's."
    334   (let ((conn (gensym)))
    335     `(let ((,conn ,connection))
    336        (handler-bind ((serious-condition
    337                         (lambda (condition)
    338                           (close-connection ,conn condition (safe-backtrace))
    339                           (abort condition))))
    340          . ,body))))
    341 
    342 (add-hook *new-connection-hook* 'notify-backend-of-connection)
    343 (defun notify-backend-of-connection (connection)
    344   (declare (ignore connection))
    345   (emacs-connected))
    346 
    347 
    348 ;;;; Utilities
    349 
    350 ;; stolen from Hunchentoot
    351 (defmacro defvar-unbound (name &optional (doc-string ""))
    352   "Convenience macro to declare unbound special variables with a
    353 documentation string."
    354   `(progn
    355      (defvar ,name)
    356      (setf (documentation ',name 'variable) ,doc-string)
    357      ',name))
    358 
    359 
    360 ;;;;; Logging
    361 
    362 (defvar *slynk-io-package*
    363   (let ((package (make-package :slynk-io-package :use '())))
    364     (import '(nil t quote) package)
    365     package))
    366 
    367 (defvar *log-events* nil)
    368 (defvar *log-output* nil) ; should be nil for image dumpers
    369 
    370 (defun init-log-output ()
    371   (unless *log-output*
    372     (setq *log-output* (real-output-stream *error-output*))))
    373 
    374 (add-hook *after-init-hook* 'init-log-output)
    375 
    376 (defun real-input-stream (stream)
    377   (typecase stream
    378     (synonym-stream
    379      (real-input-stream (symbol-value (synonym-stream-symbol stream))))
    380     (two-way-stream
    381      (real-input-stream (two-way-stream-input-stream stream)))
    382     (t stream)))
    383 
    384 (defun real-output-stream (stream)
    385   (typecase stream
    386     (synonym-stream
    387      (real-output-stream (symbol-value (synonym-stream-symbol stream))))
    388     (two-way-stream
    389      (real-output-stream (two-way-stream-output-stream stream)))
    390     (t stream)))
    391 
    392 (defvar *event-history* (make-array 40 :initial-element nil)
    393   "A ring buffer to record events for better error messages.")
    394 (defvar *event-history-index* 0)
    395 (defvar *enable-event-history* t)
    396 
    397 (defun log-event (format-string &rest args)
    398   "Write a message to *terminal-io* when *log-events* is non-nil.
    399 Useful for low level debugging."
    400   (with-standard-io-syntax
    401     (let ((*print-readably* nil)
    402           (*print-pretty* nil)
    403           (*package* *slynk-io-package*))
    404       (when *enable-event-history*
    405         (setf (aref *event-history* *event-history-index*)
    406               (format nil "~?" format-string args))
    407         (setf *event-history-index*
    408               (mod (1+ *event-history-index*) (length *event-history*))))
    409       (when *log-events*
    410         (write-string (escape-non-ascii (format nil "~?" format-string args))
    411                       *log-output*)
    412         (force-output *log-output*)))))
    413 
    414 (defun event-history-to-list ()
    415   "Return the list of events (older events first)."
    416   (let ((arr *event-history*)
    417         (idx *event-history-index*))
    418     (concatenate 'list (subseq arr idx) (subseq arr 0 idx))))
    419 
    420 (defun clear-event-history ()
    421   (fill *event-history* nil)
    422   (setq *event-history-index* 0))
    423 
    424 (defun dump-event-history (stream)
    425   (dolist (e (event-history-to-list))
    426     (dump-event e stream)))
    427 
    428 (defun dump-event (event stream)
    429   (cond ((stringp event)
    430          (write-string (escape-non-ascii event) stream))
    431         ((null event))
    432         (t
    433          (write-string
    434           (escape-non-ascii (format nil "Unexpected event: ~A~%" event))
    435           stream))))
    436 
    437 (defun escape-non-ascii (string)
    438   "Return a string like STRING but with non-ascii chars escaped."
    439   (cond ((ascii-string-p string) string)
    440         (t (with-output-to-string (out)
    441              (loop for c across string do
    442                (cond ((ascii-char-p c) (write-char c out))
    443                      (t (format out "\\x~4,'0X" (char-code c)))))))))
    444 
    445 (defun ascii-string-p (o)
    446   (and (stringp o)
    447        (every #'ascii-char-p o)))
    448 
    449 (defun ascii-char-p (c)
    450   (<= (char-code c) 127))
    451 
    452 
    453 ;;;;; Helper macros
    454 
    455 (defmacro destructure-case (value &body patterns)
    456   "Dispatch VALUE to one of PATTERNS.
    457 A cross between `case' and `destructuring-bind'.
    458 The pattern syntax is:
    459   ((HEAD . ARGS) . BODY)
    460 The list of patterns is searched for a HEAD `eq' to the car of
    461 VALUE. If one is found, the BODY is executed with ARGS bound to the
    462 corresponding values in the CDR of VALUE."
    463   (let ((operator (gensym "op-"))
    464 	(operands (gensym "rand-"))
    465 	(tmp (gensym "tmp-")))
    466     `(let* ((,tmp ,value)
    467 	    (,operator (car ,tmp))
    468 	    (,operands (cdr ,tmp)))
    469        (case ,operator
    470          ,@(loop for (pattern . body) in patterns collect
    471                  (if (eq pattern t)
    472                      `(t ,@body)
    473                      (destructuring-bind (op &rest rands) pattern
    474                        `(,op (destructuring-bind ,rands ,operands
    475                                ,@body)))))
    476          ,@(if (eq (caar (last patterns)) t)
    477                '()
    478                `((t (error "destructure-case failed: ~S" ,tmp))))))))
    479 
    480 
    481 
    482 ;;; Channels
    483 
    484 (defmacro channels () `(connection-channels *emacs-connection*))
    485 (defmacro channel-counter () `(connection-channel-counter *emacs-connection*))
    486 
    487 (defclass channel ()
    488   ((id     :initform (incf (channel-counter))
    489            :reader channel-id)
    490    (thread :initarg :thread :initform (current-thread)
    491            :reader channel-thread)
    492    (name   :initarg :name   :initform nil)))
    493 
    494 (defmethod initialize-instance :after ((ch channel) &key)
    495   ;; FIXME: slightly fugly, but I need this to be able to name the
    496   ;; thread according to the channel's id.
    497   ;;
    498   (with-slots (thread) ch
    499     (when (use-threads-p)
    500       (setf thread (spawn-channel-thread *emacs-connection* ch)))
    501     (slynk-backend:send thread `(:serve-channel ,ch)))
    502   (setf (channels) (nconc (channels) (list ch))))
    503 
    504 (defmethod print-object ((c channel) stream)
    505   (print-unreadable-object (c stream :type t)
    506     (with-slots (id name) c
    507       (format stream "~d ~a" id name))))
    508 
    509 (defmethod drop-unprocessed-events (channel)
    510   ;; FIXME: perhaps this should incorporate most
    511   ;; behaviour from it's :after spec currently in slynk-mrepl.lisp)
    512   (declare (ignore channel)))
    513 
    514 (defun find-channel (id)
    515   (find id (channels) :key #'channel-id))
    516 
    517 (defun find-channel-thread (channel)
    518   (channel-thread channel))
    519 
    520 (defun channel-thread-id (channel)
    521   (slynk-backend:thread-id (channel-thread channel)))
    522 
    523 (defmethod close-channel (channel &key)
    524   (let ((probe (find-channel (channel-id channel))))
    525     (cond (probe (setf (channels) (delete probe (channels))))
    526           (t (error "Can't close invalid channel: ~a" channel)))))
    527 
    528 (defgeneric channel-send (channel selector args)
    529   (:documentation "Send to CHANNEL the message SELECTOR with ARGS."))
    530 
    531 (defmacro define-channel-method (selector (channel &rest args) &body body)
    532   `(defmethod channel-send (,channel (selector (eql ',selector)) args)
    533      (destructuring-bind ,args args
    534        . ,body)))
    535 
    536 (define-channel-method :teardown ((c channel))
    537   (if (use-threads-p)
    538       ;; eventually calls CLOSE-CHANNEL
    539       (throw 'stop-processing 'listener-teardown)
    540       (close-channel c)))
    541 
    542 (defun send-to-remote-channel (channel-id msg)
    543   (send-to-emacs `(:channel-send ,channel-id ,msg)))
    544 
    545 
    546 ;;; Listeners
    547 (defclass listener ()
    548   ((out :initarg :out :type stream :reader listener-out)
    549    (in  :initarg :in :type stream :reader listener-in)
    550    (env)))
    551 
    552 (defmacro listeners () `(connection-listeners *emacs-connection*))
    553 
    554 (defmethod initialize-instance :after ((l listener) &key initial-env) 
    555   (with-slots (out in env) l
    556     (let ((io (make-two-way-stream in out)))
    557       (setf env
    558             (append
    559              initial-env
    560              `((cl:*standard-output* . ,out)
    561                (cl:*standard-input*  . ,in)
    562                (cl:*trace-output*    . ,out)
    563                (cl:*error-output*    . ,out)
    564                (cl:*debug-io*        . ,io)
    565                (cl:*query-io*        . ,io)
    566                (cl:*terminal-io*     . ,io)))))
    567     (assert out nil "Must have an OUT stream")
    568     (assert in nil "Must have an IN stream")
    569     (assert env nil "Must have an ENV"))
    570   (setf (listeners) (nconc (listeners)
    571                            (list l))))
    572 
    573 (defun call-with-listener (listener fn &optional saving)
    574   (with-slots (env) listener
    575     (with-bindings env
    576       (unwind-protect (funcall fn)
    577         (when saving
    578           (loop for binding in env
    579                 do (setf (cdr binding) (symbol-value (car binding)))))))))
    580 
    581 (defmacro with-listener-bindings (listener &body body)
    582   "Execute BODY inside LISTENER's environment"
    583   `(call-with-listener ,listener (lambda () ,@body)))
    584 
    585 (defmacro saving-listener-bindings (listener &body body)
    586   "Execute BODY inside LISTENER's environment, update it afterwards."
    587   `(call-with-listener ,listener (lambda () ,@body) 'saving))
    588 
    589 (defmacro with-default-listener ((connection) &body body)
    590   "Execute BODY with in CONNECTION's default listener."
    591   (let ((listener-sym (gensym))
    592         (body-fn-sym (gensym)))
    593     `(let ((,listener-sym (default-listener ,connection))
    594            (,body-fn-sym #'(lambda () ,@body)))
    595        (if ,listener-sym
    596            (with-listener-bindings ,listener-sym
    597              (funcall ,body-fn-sym))
    598            (funcall ,body-fn-sym)))))
    599 
    600 (defun default-listener (connection)
    601   (first (connection-listeners connection)))
    602 
    603 (defun flush-listener-streams (listener)
    604   (with-slots (in out) listener
    605     (force-output out)
    606     #-armedbear
    607     (slynk-gray::reset-stream-line-column out)
    608     (clear-input in)))
    609 
    610 (defmethod close-listener (l)
    611   (with-slots (in out) l (close in) (close out))
    612   (setf (listeners) (delete l (listeners))))
    613 
    614 
    615 ;;;; Interrupt handling
    616 
    617 ;; Usually we'd like to enter the debugger when an interrupt happens.
    618 ;; But for some operations, in particular send&receive, it's crucial
    619 ;; that those are not interrupted when the mailbox is in an
    620 ;; inconsistent/locked state. Obviously, if send&receive don't work we
    621 ;; can't communicate and the debugger will not work.  To solve that
    622 ;; problem, we try to handle interrupts only at certain safe-points.
    623 ;;
    624 ;; Whenever an interrupt happens we call the function
    625 ;; INVOKE-OR-QUEUE-INTERRUPT.  Usually this simply invokes the
    626 ;; debugger, but if interrupts are disabled the interrupt is put in a
    627 ;; queue for later processing.  At safe-points, we call
    628 ;; CHECK-SLY-INTERRUPTS which looks at the queue and invokes the
    629 ;; debugger if needed.
    630 ;;
    631 ;; The queue for interrupts is stored in a thread local variable.
    632 ;; WITH-CONNECTION sets it up.  WITH-SLY-INTERRUPTS allows
    633 ;; interrupts, i.e. the debugger is entered immediately.  When we call
    634 ;; "user code" or non-problematic code we allow interrupts.  When
    635 ;; inside WITHOUT-SLY-INTERRUPTS, interrupts are queued.  When we
    636 ;; switch from "user code" to more delicate operations we need to
    637 ;; disable interrupts.  In particular, interrupts should be disabled
    638 ;; for SEND and RECEIVE-IF.
    639 
    640 ;; If true execute interrupts, otherwise queue them.
    641 ;; Note: `with-connection' binds *pending-sly-interrupts*.
    642 (defvar *sly-interrupts-enabled*)
    643 
    644 (defmacro with-interrupts-enabled% (flag body)
    645   `(progn
    646      ,@(if flag '((check-sly-interrupts)))
    647      (multiple-value-prog1
    648          (let ((*sly-interrupts-enabled* ,flag))
    649            ,@body)
    650        ,@(if flag '((check-sly-interrupts))))))
    651 
    652 (defmacro with-sly-interrupts (&body body)
    653   `(with-interrupts-enabled% t ,body))
    654 
    655 (defmacro without-sly-interrupts (&body body)
    656   `(with-interrupts-enabled% nil ,body))
    657 
    658 (defun queue-thread-interrupt (thread function)
    659   (interrupt-thread thread
    660                     (lambda ()
    661                       ;; safely interrupt THREAD
    662                       (when (invoke-or-queue-interrupt function)
    663                         (wake-thread thread)))))
    664 
    665 (defun invoke-or-queue-interrupt (function)
    666   (log-event "invoke-or-queue-interrupt: ~a~%" function)
    667   (cond ((not (boundp '*sly-interrupts-enabled*))
    668          (without-sly-interrupts
    669            (funcall function)))
    670         (*sly-interrupts-enabled*
    671          (log-event "interrupts-enabled~%")
    672          (funcall function))
    673         (t
    674          (setq *pending-sly-interrupts*
    675                (nconc *pending-sly-interrupts*
    676                       (list function)))
    677          (cond ((cdr *pending-sly-interrupts*)
    678                 (log-event "too many queued interrupts~%")
    679                 (with-simple-restart (continue "Continue from interrupt")
    680                   (handler-bind ((serious-condition #'invoke-sly-debugger))
    681                     (check-sly-interrupts))))
    682                (t
    683                 (log-event "queue-interrupt: ~a~%" function)
    684                 (when *interrupt-queued-handler*
    685                   (funcall *interrupt-queued-handler*))
    686                 t)))))
    687 
    688 ;; Thread local variable used for flow-control.
    689 ;; It's bound by `with-connection'.
    690 (defvar *send-counter*)
    691 
    692 (defmacro with-connection ((connection) &body body)
    693   "Execute BODY in the context of CONNECTION."
    694   `(let ((connection ,connection)
    695          (function (lambda () . ,body)))
    696      (if (eq *emacs-connection* connection)
    697          (funcall function)
    698          (let ((*emacs-connection* connection)
    699                (*pending-sly-interrupts* '())
    700                (*send-counter* 0))
    701            (without-sly-interrupts
    702              (with-slynk-error-handler (connection)
    703                (with-default-listener (connection)
    704                  (call-with-debugger-hook #'slynk-debugger-hook
    705                                           function))))))))
    706 
    707 (defun call-with-retry-restart (msg thunk)
    708   (loop (with-simple-restart (retry "~a" msg)
    709           (return (funcall thunk)))))
    710 
    711 (defmacro with-retry-restart ((&key (msg "Retry.")) &body body)
    712   (check-type msg string)
    713   `(call-with-retry-restart ,msg (lambda () ,@body)))
    714 
    715 
    716 ;;;;; Sentinel
    717 ;;;
    718 ;;; The sentinel thread manages some global lists.
    719 ;;; FIXME: Overdesigned?
    720 
    721 (defvar *connections* '()
    722   "List of all active connections, with the most recent at the front.")
    723 
    724 (defvar *servers* '()
    725   "A list ((server-socket port thread) ...) describing the listening sockets.
    726 Used to close sockets on server shutdown or restart.")
    727 
    728 ;; FIXME: we simply access the global variable here.  We could ask the
    729 ;; sentinel thread instead but then we still have the problem that the
    730 ;; connection could be closed before we use it.
    731 (defun default-connection ()
    732   "Return the 'default' Emacs connection.
    733 This connection can be used to talk with Emacs when no specific
    734 connection is in use, i.e. *EMACS-CONNECTION* is NIL.
    735 
    736 The default connection is defined (quite arbitrarily) as the most
    737 recently established one."
    738   (car *connections*))
    739 
    740 (defun start-sentinel ()
    741   (unless (find-registered 'sentinel)
    742     (let ((thread (spawn #'sentinel :name "Slynk Sentinel")))
    743       (register-thread 'sentinel thread))))
    744 
    745 (defun sentinel ()
    746   (catch 'exit-sentinel
    747     (loop (sentinel-serve (receive)))))
    748 
    749 (defun send-to-sentinel (msg)
    750   (let ((sentinel (find-registered 'sentinel)))
    751     (cond (sentinel (send sentinel msg))
    752           (t (sentinel-serve msg)))))
    753 
    754 (defun sentinel-serve (msg)
    755   (destructure-case msg
    756     ((:add-connection conn)
    757      (push conn *connections*))
    758     ((:close-connection connection condition backtrace)
    759      (close-connection% connection condition backtrace)
    760      (sentinel-maybe-exit))
    761     ((:add-server socket port thread)
    762      (push (list socket port thread) *servers*))
    763     ((:stop-server key port)
    764      (sentinel-stop-server key port)
    765      (sentinel-maybe-exit))))
    766 
    767 (defun sentinel-stop-server (key value)
    768   (let ((probe (find value *servers* :key (ecase key
    769                                             (:socket #'car)
    770                                             (:port #'cadr)))))
    771     (cond (probe
    772            (setq *servers* (delete probe *servers*))
    773            (destructuring-bind (socket _port thread) probe
    774              (declare (ignore _port))
    775              (ignore-errors (close-socket socket))
    776              (when (and thread
    777                         (thread-alive-p thread)
    778                         (not (eq thread (current-thread))))
    779                (ignore-errors (kill-thread thread)))))
    780           (t
    781            (warn "No server for ~s: ~s" key value)))))
    782 
    783 (defun sentinel-maybe-exit ()
    784   (when (and (null *connections*)
    785              (null *servers*)
    786              (and (current-thread)
    787                   (eq (find-registered 'sentinel)
    788                       (current-thread))))
    789     (register-thread 'sentinel nil)
    790     (throw 'exit-sentinel nil)))
    791 
    792 
    793 ;;;;; Misc
    794 
    795 (defun use-threads-p ()
    796   (eq (connection-communication-style *emacs-connection*) :spawn))
    797 
    798 (defun current-thread-id ()
    799   (thread-id (current-thread)))
    800 
    801 (declaim (inline ensure-list))
    802 (defun ensure-list (thing)
    803   (if (listp thing) thing (list thing)))
    804 
    805 
    806 ;;;;; Symbols
    807 
    808 ;; FIXME: this docstring is more confusing than helpful.
    809 (defun symbol-status (symbol &optional (package (symbol-package symbol)))
    810   "Returns one of
    811 
    812   :INTERNAL  if the symbol is _present_ in PACKAGE as an _internal_ symbol,
    813 
    814   :EXTERNAL  if the symbol is _present_ in PACKAGE as an _external_ symbol,
    815 
    816   :INHERITED if the symbol is _inherited_ by PACKAGE through USE-PACKAGE,
    817              but is not _present_ in PACKAGE,
    818 
    819   or NIL     if SYMBOL is not _accessible_ in PACKAGE.
    820 
    821 
    822 Be aware not to get confused with :INTERNAL and how \"internal
    823 symbols\" are defined in the spec; there is a slight mismatch of
    824 definition with the Spec and what's commonly meant when talking
    825 about internal symbols most times. As the spec says:
    826 
    827   In a package P, a symbol S is
    828 
    829      _accessible_  if S is either _present_ in P itself or was
    830                    inherited from another package Q (which implies
    831                    that S is _external_ in Q.)
    832 
    833         You can check that with: (AND (SYMBOL-STATUS S P) T)
    834 
    835 
    836      _present_     if either P is the /home package/ of S or S has been
    837                    imported into P or exported from P by IMPORT, or
    838                    EXPORT respectively.
    839 
    840                    Or more simply, if S is not _inherited_.
    841 
    842         You can check that with: (LET ((STATUS (SYMBOL-STATUS S P)))
    843                                    (AND STATUS
    844                                         (NOT (EQ STATUS :INHERITED))))
    845 
    846 
    847      _external_    if S is going to be inherited into any package that
    848                    /uses/ P by means of USE-PACKAGE, MAKE-PACKAGE, or
    849                    DEFPACKAGE.
    850 
    851                    Note that _external_ implies _present_, since to
    852                    make a symbol _external_, you'd have to use EXPORT
    853                    which will automatically make the symbol _present_.
    854 
    855         You can check that with: (EQ (SYMBOL-STATUS S P) :EXTERNAL)
    856 
    857 
    858      _internal_    if S is _accessible_ but not _external_.
    859 
    860         You can check that with: (LET ((STATUS (SYMBOL-STATUS S P)))
    861                                    (AND STATUS
    862                                         (NOT (EQ STATUS :EXTERNAL))))
    863 
    864 
    865         Notice that this is *different* to
    866                                  (EQ (SYMBOL-STATUS S P) :INTERNAL)
    867         because what the spec considers _internal_ is split up into two
    868         explicit pieces: :INTERNAL, and :INHERITED; just as, for instance,
    869         CL:FIND-SYMBOL does.
    870 
    871         The rationale is that most times when you speak about \"internal\"
    872         symbols, you're actually not including the symbols inherited
    873         from other packages, but only about the symbols directly specific
    874         to the package in question.
    875 "
    876   (when package     ; may be NIL when symbol is completely uninterned.
    877     (check-type symbol symbol) (check-type package package)
    878     (multiple-value-bind (present-symbol status)
    879         (find-symbol (symbol-name symbol) package)
    880       (and (eq symbol present-symbol) status))))
    881 
    882 (defun symbol-external-p (symbol &optional (package (symbol-package symbol)))
    883   "True if SYMBOL is external in PACKAGE.
    884 If PACKAGE is not specified, the home package of SYMBOL is used."
    885   (eq (symbol-status symbol package) :external))
    886 
    887 (defun classify-symbol (symbol)
    888   "Returns a list of classifiers that classify SYMBOL according to its
    889 underneath objects (e.g. :BOUNDP if SYMBOL constitutes a special
    890 variable.) The list may contain the following classification
    891 keywords: :BOUNDP, :FBOUNDP, :CONSTANT, :GENERIC-FUNCTION,
    892 :TYPESPEC, :CLASS, :MACRO, :SPECIAL-OPERATOR, and/or :PACKAGE"
    893   (check-type symbol symbol)
    894   (flet ((type-specifier-p (s)
    895            (or (documentation s 'type)
    896                (not (eq (type-specifier-arglist s) :not-available)))))
    897     (let (result)
    898       (when (boundp symbol)             (push (if (constantp symbol)
    899                                                   :constant :boundp) result))
    900       (when (fboundp symbol)            (push :fboundp result))
    901       (when (type-specifier-p symbol)   (push :typespec result))
    902       (when (find-class symbol nil)     (push :class result))
    903       (when (macro-function symbol)     (push :macro result))
    904       (when (special-operator-p symbol) (push :special-operator result))
    905       (when (find-package symbol)       (push :package result))
    906       (when (and (fboundp symbol)
    907                  (typep (ignore-errors (fdefinition symbol))
    908                         'generic-function))
    909         (push :generic-function result))
    910       result)))
    911 
    912 
    913 ;;;; TCP Server
    914 
    915 (defvar *communication-style* (preferred-communication-style))
    916 
    917 (defvar *dont-close* nil
    918   "Default value of :dont-close argument to start-server and
    919   create-server.")
    920 
    921 (defparameter *loopback-interface* "localhost")
    922 
    923 (defun start-server (port-file
    924                      &key (style *communication-style*)
    925                        (dont-close *dont-close*))
    926   "Start the server and write the listen port number to PORT-FILE.
    927 This is the entry point for Emacs."
    928   (setq *m-x-sly-from-emacs* t)
    929   (setup-server 0
    930                 (lambda (port) (announce-server-port port-file port))
    931                 style dont-close nil))
    932 
    933 (defun create-server (&key (port default-server-port)
    934                         (style *communication-style*)
    935                         (dont-close *dont-close*)
    936                         interface
    937                         backlog)
    938   "Start a SLYNK server on PORT running in STYLE.
    939 If DONT-CLOSE is true then the listen socket will accept multiple
    940 connections, otherwise it will be closed after the first.
    941 
    942 Optionally, an INTERFACE could be specified and swank will bind
    943 the PORT on this interface. By default, interface is \"localhost\"."
    944   (let ((*loopback-interface* (or interface
    945                                   *loopback-interface*)))
    946     (setup-server port #'simple-announce-function
    947                   style dont-close backlog)))
    948 
    949 (defun find-external-format-or-lose (coding-system)
    950   (or (find-external-format coding-system)
    951       (error "Unsupported coding system: ~s" coding-system)))
    952 
    953 (defmacro restart-loop (form &body clauses)
    954   "Executes FORM, with restart-case CLAUSES which have a chance to modify FORM's
    955 environment before trying again (by returning normally) or giving up (through an
    956 explicit transfer of control), all within an implicit block named nil.
    957 e.g.: (restart-loop (http-request url) (use-value (new) (setq url new)))"
    958   `(loop (restart-case (return ,form) ,@clauses)))
    959 
    960 (defun socket-quest (port backlog)
    961   "Attempt o create a socket on PORT.
    962 Add a restart, prompting user to enter a new port if PORT is already
    963 taken."
    964   (restart-loop (create-socket *loopback-interface* port :backlog backlog)
    965     (use-value (&optional (new-port (1+ port)))
    966       :report (lambda (stream) (format stream "Try a port other than ~D" port))
    967       :interactive
    968       (lambda ()
    969         (format *query-io* "Enter port (defaults to ~D): " (1+ port))
    970         (finish-output *query-io*)      ; necessary for tunnels
    971         (ignore-errors (list (parse-integer (read-line *query-io*)))))
    972       (setq port new-port))))
    973 
    974 (defun setup-server (port announce-fn style dont-close backlog)
    975   (init-log-output)
    976   (let* ((socket (socket-quest port backlog))
    977          (port (local-port socket)))
    978     (funcall announce-fn port)
    979     (labels ((serve () (accept-connections socket style dont-close))
    980              (note () (send-to-sentinel `(:add-server ,socket ,port
    981                                                       ,(current-thread))))
    982              (serve-loop () (note) (loop do (serve) while dont-close)))
    983       (ecase style
    984         (:spawn (initialize-multiprocessing
    985                  (lambda ()
    986                    (start-sentinel)
    987                    (spawn #'serve-loop :name (format nil "Slynk ~s" port)))))
    988         ((:fd-handler :sigio)
    989          (note)
    990          (add-fd-handler socket #'serve))
    991         ((nil) (serve-loop))))
    992     port))
    993 
    994 (defun stop-server (port)
    995   "Stop server running on PORT."
    996   (send-to-sentinel `(:stop-server :port ,port)))
    997 
    998 (defun restart-server (&key (port default-server-port)
    999                        (style *communication-style*)
   1000                        (dont-close *dont-close*))
   1001   "Stop the server listening on PORT, then start a new SLYNK server
   1002 on PORT running in STYLE. If DONT-CLOSE is true then the listen socket
   1003 will accept multiple connections, otherwise it will be closed after the
   1004 first."
   1005   (stop-server port)
   1006   (sleep 5)
   1007   (create-server :port port :style style :dont-close dont-close))
   1008 
   1009 (defun accept-connections (socket style dont-close)
   1010   (unwind-protect
   1011        (let ((client (accept-connection socket :external-format nil
   1012                                                :buffering t)))
   1013          (authenticate-client client)
   1014          (serve-requests (make-connection socket client style)))
   1015     (unless dont-close
   1016       (send-to-sentinel `(:stop-server :socket ,socket)))))
   1017 
   1018 (defun authenticate-client (stream)
   1019   (let ((secret (sly-secret)))
   1020     (when secret
   1021       (set-stream-timeout stream 20)
   1022       (let ((first-val (read-packet stream)))
   1023         (unless (and (stringp first-val) (string= first-val secret))
   1024           (error "Incoming connection doesn't know the password.")))
   1025       (set-stream-timeout stream nil))))
   1026 
   1027 (defun sly-secret ()
   1028   "Finds the magic secret from the user's home directory.  Returns nil
   1029 if the file doesn't exist; otherwise the first line of the file."
   1030   (with-open-file (in
   1031                    (merge-pathnames (user-homedir-pathname) #p".sly-secret")
   1032                    :if-does-not-exist nil)
   1033     (and in (read-line in nil ""))))
   1034 
   1035 (defun serve-requests (connection)
   1036   "Read and process all requests on connections."
   1037   (etypecase connection
   1038     (multithreaded-connection
   1039      (spawn-threads-for-connection connection))
   1040     (singlethreaded-connection
   1041      (ecase (connection-communication-style connection)
   1042        ((nil) (simple-serve-requests connection))
   1043        (:sigio (install-sigio-handler connection))
   1044        (:fd-handler (install-fd-handler connection))))))
   1045 
   1046 (defun stop-serving-requests (connection)
   1047   (etypecase connection
   1048     (multithreaded-connection
   1049      (cleanup-connection-threads connection))
   1050     (singlethreaded-connection
   1051      (ecase (connection-communication-style connection)
   1052        ((nil))
   1053        (:sigio (deinstall-sigio-handler connection))
   1054        (:fd-handler (deinstall-fd-handler connection))))))
   1055 
   1056 (defun announce-server-port (file port)
   1057   (with-open-file (s file
   1058                      :direction :output
   1059                      :if-exists :error
   1060                      :if-does-not-exist :create)
   1061     (format s "~S~%" port))
   1062   (simple-announce-function port))
   1063 
   1064 (defun simple-announce-function (port)
   1065   (when *slynk-debug-p*
   1066     (format *log-output* "~&;; Slynk started at port: ~D.~%" port)
   1067     (force-output *log-output*)))
   1068 
   1069 
   1070 ;;;;; Event Decoding/Encoding
   1071 
   1072 (defun decode-message (stream)
   1073   "Read an S-expression from STREAM using the SLY protocol."
   1074   (log-event "decode-message~%")
   1075   (without-sly-interrupts
   1076     (handler-bind ((error #'signal-slynk-error))
   1077       (handler-case (read-message stream *slynk-io-package*)
   1078         (slynk-reader-error (c)
   1079           `(:reader-error ,(slynk-reader-error.packet c)
   1080                           ,(slynk-reader-error.cause c)))))))
   1081 
   1082 (defun encode-message (message stream)
   1083   "Write an S-expression to STREAM using the SLY protocol."
   1084   (log-event "encode-message~%")
   1085   (without-sly-interrupts
   1086     (handler-bind ((error #'signal-slynk-error))
   1087       (write-message message *slynk-io-package* stream))))
   1088 
   1089 
   1090 ;;;;; Event Processing
   1091 
   1092 (defvar *sly-db-quit-restart* nil
   1093   "The restart that will be invoked when the user calls sly-db-quit.")
   1094 
   1095 ;; Establish a top-level restart and execute BODY.
   1096 ;; Execute K if the restart is invoked.
   1097 (defmacro with-top-level-restart ((connection k) &body body)
   1098   `(with-connection (,connection)
   1099      (restart-case
   1100          (let ((*sly-db-quit-restart* (find-restart 'abort)))
   1101            ,@body)
   1102        (abort (&optional v)
   1103          :report "Return to SLY's top level."
   1104          (declare (ignore v))
   1105          (force-user-output)
   1106          ,k))))
   1107 
   1108 (defun handle-requests (connection &optional timeout)
   1109   "Read and process :emacs-rex requests.
   1110 The processing is done in the extent of the toplevel restart."
   1111   (with-connection (connection)
   1112     (cond (*sly-db-quit-restart*
   1113            (process-requests timeout))
   1114           (t
   1115            (tagbody
   1116             start
   1117               (with-top-level-restart (connection (go start))
   1118                 (process-requests timeout)))))))
   1119 
   1120 (defvar-unbound *channel*
   1121   "Current CHANNEL instance used by :EMACS-CHANNEL-SEND messages.")
   1122 
   1123 (defun process-requests (timeout)
   1124   "Read and process requests from Emacs.
   1125 TIMEOUT has the same meaning as in WAIT-FOR-EVENT."
   1126   (catch 'stop-processing
   1127     (loop
   1128       (multiple-value-bind (event timed-out-p)
   1129           (wait-for-event `(or (:emacs-rex . _)
   1130                                (:emacs-channel-send . _))
   1131                           timeout)
   1132         (when timed-out-p (return))
   1133         (destructure-case event
   1134           ((:emacs-rex &rest args) (apply #'eval-for-emacs args))
   1135           ((:emacs-channel-send *channel* (selector &rest args))
   1136            (channel-send *channel* selector args)))))))
   1137 
   1138 (defun spawn-channel-thread (connection channel)
   1139   "Spawn a listener thread for CONNECTION and CHANNEL.
   1140 
   1141 The new thread will block waiting for a :SERVE-CHANNEL message, then
   1142 process all requests in series until the :TEARDOWN message, at which
   1143 point the thread terminates and CHANNEL is closed."
   1144   (slynk-backend:spawn
   1145    (lambda ()
   1146      (with-connection (connection)
   1147        (unwind-protect
   1148             (destructure-case
   1149                 (slynk-backend:receive)
   1150               ((:serve-channel c)
   1151                (assert (eq c channel))
   1152                (loop
   1153                  (with-top-level-restart (connection
   1154                                           (drop-unprocessed-events channel))
   1155                    (when (eq (process-requests nil)
   1156                              'listener-teardown)
   1157                      (return))))))
   1158          (close-channel channel))))
   1159    :name (with-slots (id name) channel
   1160            (format nil "sly-channel-~a-~a" id name))))
   1161 
   1162 
   1163 (defun current-socket-io ()
   1164   (connection-socket-io *emacs-connection*))
   1165 
   1166 (defun close-connection (connection condition backtrace)
   1167   (send-to-sentinel `(:close-connection ,connection ,condition ,backtrace)))
   1168 
   1169 (defun close-connection% (c condition backtrace)
   1170   (let ((*debugger-hook* nil))
   1171     (log-event "close-connection: ~a ...~%" condition)
   1172     (format *log-output* "~&;; slynk:close-connection: ~A~%"
   1173             (escape-non-ascii (safe-condition-message condition)))
   1174     (let ((*emacs-connection* c))
   1175       (format *log-output* "~&;; closing ~a channels~%" (length (connection-channels c)))
   1176       (mapc #'(lambda (c) (close-channel c :force t)) (connection-channels c))
   1177       (format *log-output* "~&;; closing ~a listeners~%" (length (connection-listeners c)))
   1178       (ignore-errors
   1179        (mapc #'close-listener (connection-listeners c))))
   1180     (stop-serving-requests c)
   1181     (close (connection-socket-io c))
   1182     (setf *connections* (remove c *connections*))
   1183     (run-hook *connection-closed-hook* c)
   1184     (when (and condition (not (typep condition 'end-of-file)))
   1185       (finish-output *log-output*)
   1186       (format *log-output* "~&;; Event history start:~%")
   1187       (dump-event-history *log-output*)
   1188       (format *log-output* "~
   1189 ;; Event history end.~%~
   1190 ;; Backtrace:~%~{~A~%~}~
   1191 ;; Connection to Emacs lost. [~%~
   1192 ;;  condition: ~A~%~
   1193 ;;  type: ~S~%~
   1194 ;;  style: ~S]~%"
   1195               (loop for (i f) in backtrace
   1196                     collect
   1197                     (ignore-errors
   1198                      (format nil "~d: ~a" i (escape-non-ascii f))))
   1199               (escape-non-ascii (safe-condition-message condition) )
   1200               (type-of condition)
   1201               (connection-communication-style c)))
   1202     (finish-output *log-output*)
   1203     (log-event "close-connection ~a ... done.~%" condition)))
   1204 
   1205 ;;;;;; Thread based communication
   1206 
   1207 (defun read-loop (connection)
   1208   (let ((input-stream (connection-socket-io connection))
   1209         (control-thread (mconn.control-thread connection)))
   1210     (with-slynk-error-handler (connection)
   1211       (loop (send control-thread (decode-message input-stream))))))
   1212 
   1213 (defun dispatch-loop (connection)
   1214   (let ((*emacs-connection* connection))
   1215     (with-panic-handler (connection)
   1216       (loop (dispatch-event connection (receive))))))
   1217 
   1218 (defgeneric thread-for-evaluation (connection id)
   1219   (:documentation "Find or create a thread to evaluate the next request.")
   1220   (:method ((connection multithreaded-connection) (id (eql t)))
   1221     (spawn-worker-thread connection))
   1222   (:method ((connection multithreaded-connection) (id (eql :find-existing)))
   1223     (car (mconn.active-threads connection)))
   1224   (:method (connection (id integer))
   1225     (declare (ignorable connection))
   1226     (find-thread id))
   1227   (:method ((connection singlethreaded-connection) id)
   1228     (declare (ignorable connection connection id))
   1229     (current-thread)))
   1230 
   1231 (defun interrupt-worker-thread (connection id)
   1232   (let ((thread (thread-for-evaluation connection
   1233                                        (cond ((eq id t) :find-existing)
   1234                                              (t id)))))
   1235     (log-event "interrupt-worker-thread: ~a ~a~%" id thread)
   1236     (if thread
   1237         (etypecase connection
   1238           (multithreaded-connection
   1239            (queue-thread-interrupt thread #'simple-break))
   1240           (singlethreaded-connection
   1241            (simple-break)))
   1242         (encode-message (list :debug-condition (current-thread-id)
   1243                               (format nil "Thread with id ~a not found"
   1244                                       id))
   1245                         (current-socket-io)))))
   1246 
   1247 (defun spawn-worker-thread (connection)
   1248   (spawn (lambda ()
   1249            (with-bindings *default-worker-thread-bindings*
   1250              (with-top-level-restart (connection nil)
   1251                (let ((thread (current-thread)))
   1252                  (unwind-protect
   1253                       (apply #'eval-for-emacs
   1254                              (cdr (wait-for-event `(:emacs-rex . _))))
   1255                    (remove-active-thread connection thread))))))
   1256          :name "slynk-worker"))
   1257 
   1258 (defun add-active-thread (connection thread)
   1259   (etypecase connection
   1260     (multithreaded-connection
   1261      (push thread (mconn.active-threads connection)))
   1262     (singlethreaded-connection)))
   1263 
   1264 (defun remove-active-thread (connection thread)
   1265   (etypecase connection
   1266     (multithreaded-connection
   1267      (setf (mconn.active-threads connection)
   1268            (delete thread (mconn.active-threads connection) :count 1)))
   1269     (singlethreaded-connection)))
   1270 
   1271 (defun dispatch-event (connection event)
   1272   "Handle an event triggered either by Emacs or within Lisp."
   1273   (log-event "dispatch-event: ~s~%" event)
   1274   (destructure-case event
   1275     ((:emacs-rex form package thread-id id &rest extra-rex-options)
   1276      (let ((thread (thread-for-evaluation connection thread-id)))
   1277        (cond (thread
   1278               (add-active-thread connection thread)
   1279               (send-event thread `(:emacs-rex ,form ,package ,id ,@extra-rex-options)))
   1280              (t
   1281               (encode-message
   1282                (list :invalid-rpc id
   1283                      (format nil "Thread not found: ~s" thread-id))
   1284                (current-socket-io))))))
   1285     ((:return thread &rest args)
   1286      (declare (ignore thread))
   1287      (encode-message `(:return ,@args) (current-socket-io)))
   1288     ((:emacs-interrupt thread-id)
   1289      (interrupt-worker-thread connection thread-id))
   1290     (((:write-string
   1291        :debug :debug-condition :debug-activate :debug-return :channel-send
   1292        :presentation-start :presentation-end
   1293        :new-package :new-features :ed :indentation-update
   1294        :eval :eval-no-wait :background-message :inspect :ping
   1295        :y-or-n-p :read-from-minibuffer :read-string :read-aborted :test-delay)
   1296       &rest _)
   1297      (declare (ignore _))
   1298      (encode-message event (current-socket-io)))
   1299     (((:emacs-pong :emacs-return :emacs-return-string) thread-id &rest args)
   1300      (send-event (find-thread thread-id) (cons (car event) args)))
   1301     ((:emacs-channel-send channel-id msg)
   1302      (let* ((ch (find-channel channel-id))
   1303             (thread (and ch (find-channel-thread ch))))
   1304        (cond ((and ch thread)
   1305               (send-event thread `(:emacs-channel-send ,ch ,msg)))
   1306              (ch
   1307               (encode-message 
   1308                (list :invalid-channel channel-id
   1309                      "No suitable threads for channel")
   1310                (current-socket-io)))
   1311              (t
   1312               (encode-message 
   1313                (list :invalid-channel channel-id "Channel not found")
   1314                (current-socket-io))))))
   1315     ((:reader-error packet condition)
   1316      (encode-message `(:reader-error ,packet
   1317                                      ,(safe-condition-message condition))
   1318                      (current-socket-io)))))
   1319 
   1320 
   1321 (defun send-event (thread event)
   1322   (log-event "send-event: ~s ~s~%" thread event)
   1323   (let ((c *emacs-connection*))
   1324     (etypecase c
   1325       (multithreaded-connection
   1326        (send thread event))
   1327       (singlethreaded-connection
   1328        (setf (sconn.event-queue c) (nconc (sconn.event-queue c) (list event)))
   1329        (setf (sconn.events-enqueued c) (mod (1+ (sconn.events-enqueued c))
   1330                                             most-positive-fixnum))))))
   1331 
   1332 (defun send-to-emacs (event)
   1333   "Send EVENT to Emacs."
   1334   ;;(log-event "send-to-emacs: ~a" event)
   1335   (without-sly-interrupts
   1336     (let ((c *emacs-connection*))
   1337       (etypecase c
   1338         (multithreaded-connection
   1339          (send (mconn.control-thread c) event))
   1340         (singlethreaded-connection
   1341          (dispatch-event c event)))
   1342       (maybe-slow-down))))
   1343 
   1344 (defun make-thread-bindings-aware-lambda (fn)
   1345   (let ((connection *emacs-connection*)
   1346         (send-counter *send-counter*))
   1347     (lambda (&rest args)
   1348       (let ((*emacs-connection* connection)
   1349             (*send-counter* send-counter))
   1350         (apply fn args)))))
   1351 
   1352 
   1353 ;;;;;; Flow control
   1354 
   1355 ;; After sending N (usually 100) messages we slow down and ping Emacs
   1356 ;; to make sure that everything we have sent so far was received.
   1357 
   1358 (defconstant send-counter-limit 100)
   1359 
   1360 (defun maybe-slow-down ()
   1361   (let ((counter (incf *send-counter*)))
   1362     (when (< send-counter-limit counter)
   1363       (setf *send-counter* 0)
   1364       (ping-pong))))
   1365 
   1366 (defun ping-pong ()
   1367   (let* ((tag (make-tag))
   1368          (pattern `(:emacs-pong ,tag)))
   1369     (send-to-emacs `(:ping ,(current-thread-id) ,tag))
   1370     (wait-for-event pattern)))
   1371 
   1372 
   1373 (defun wait-for-event (pattern &optional timeout)
   1374   "Scan the event queue for PATTERN and return the event.
   1375 If TIMEOUT is NIL wait until a matching event is enqued.
   1376 If TIMEOUT is T only scan the queue without waiting.
   1377 The second return value is t if the timeout expired before a matching
   1378 event was found."
   1379   (log-event "wait-for-event: ~s ~s~%" pattern timeout)
   1380   (without-sly-interrupts
   1381     (let ((c *emacs-connection*))
   1382       (etypecase c
   1383         (multithreaded-connection
   1384          (receive-if (lambda (e) (event-match-p e pattern)) timeout))
   1385         (singlethreaded-connection
   1386          (wait-for-event/event-loop c pattern timeout))))))
   1387 
   1388 (defun wait-for-event/event-loop (connection pattern timeout)
   1389   (assert (or (not timeout) (eq timeout t)))
   1390   (loop
   1391    (check-sly-interrupts)
   1392    (let ((event (poll-for-event connection pattern)))
   1393      (when event (return (car event))))
   1394    (let ((events-enqueued (sconn.events-enqueued connection))
   1395          (ready (wait-for-input (list (current-socket-io)) timeout)))
   1396      (cond ((and timeout (not ready))
   1397             (return (values nil t)))
   1398            ((or (/= events-enqueued (sconn.events-enqueued connection))
   1399                 (eq ready :interrupt))
   1400             ;; rescan event queue, interrupts may enqueue new events
   1401             )
   1402            (t
   1403             (assert (equal ready (list (current-socket-io))))
   1404             (dispatch-event connection
   1405                             (decode-message (current-socket-io))))))))
   1406 
   1407 (defun poll-for-event (connection pattern)
   1408   (let* ((c connection)
   1409          (tail (member-if (lambda (e) (event-match-p e pattern))
   1410                           (sconn.event-queue c))))
   1411     (when tail
   1412       (setf (sconn.event-queue c)
   1413             (nconc (ldiff (sconn.event-queue c) tail) (cdr tail)))
   1414       tail)))
   1415 
   1416 ;;; FIXME: Make this use SLYNK-MATCH.
   1417 (defun event-match-p (event pattern)
   1418   (cond ((or (keywordp pattern) (numberp pattern) (stringp pattern)
   1419 	     (member pattern '(nil t)))
   1420 	 (equal event pattern))
   1421 	((symbolp pattern) t)
   1422 	((consp pattern)
   1423          (case (car pattern)
   1424            ((or) (some (lambda (p) (event-match-p event p)) (cdr pattern)))
   1425            (t (and (consp event)
   1426                    (and (event-match-p (car event) (car pattern))
   1427                         (event-match-p (cdr event) (cdr pattern)))))))
   1428         (t (error "Invalid pattern: ~S" pattern))))
   1429 
   1430 
   1431 
   1432 (defun spawn-threads-for-connection (connection)
   1433   (setf
   1434    (mconn.control-thread connection)
   1435    (spawn
   1436     (lambda ()
   1437       "Spawns a reader and indentation threads, then calls DISPATCH-LOOP."
   1438       (setf (mconn.reader-thread connection) (spawn (lambda () (read-loop connection))
   1439                                                     :name "reader-thread"))
   1440       (setf (mconn.indentation-cache-thread connection)
   1441             (spawn (lambda () (indentation-cache-loop connection))
   1442                    :name "slynk-indentation-cache-thread"))
   1443       (dispatch-loop connection))
   1444     :name "control-thread"))
   1445   connection)
   1446 
   1447 (defun cleanup-connection-threads (connection)
   1448   (let* ((c connection)
   1449          (threads (list (mconn.reader-thread c)
   1450                         (mconn.control-thread c)
   1451                         (mconn.auto-flush-thread c)
   1452                         (mconn.indentation-cache-thread c))))
   1453     (dolist (thread threads)
   1454       (when (and thread
   1455                  (thread-alive-p thread)
   1456                  (not (equal (current-thread) thread)))
   1457         (ignore-errors (kill-thread thread))))))
   1458 
   1459 ;;;;;; Signal driven IO
   1460 
   1461 (defun install-sigio-handler (connection)
   1462   (add-sigio-handler (connection-socket-io connection)
   1463                      (lambda () (process-io-interrupt connection)))
   1464   (handle-requests connection t))
   1465 
   1466 (defvar *io-interupt-level* 0)
   1467 
   1468 (defun process-io-interrupt (connection)
   1469   (log-event "process-io-interrupt ~d ...~%" *io-interupt-level*)
   1470   (let ((*io-interupt-level* (1+ *io-interupt-level*)))
   1471     (invoke-or-queue-interrupt
   1472      (lambda () (handle-requests connection t))))
   1473   (log-event "process-io-interrupt ~d ... done ~%" *io-interupt-level*))
   1474 
   1475 (defun deinstall-sigio-handler (connection)
   1476   (log-event "deinstall-sigio-handler...~%")
   1477   (remove-sigio-handlers (connection-socket-io connection))
   1478   (log-event "deinstall-sigio-handler...done~%"))
   1479 
   1480 ;;;;;; SERVE-EVENT based IO
   1481 
   1482 (defun install-fd-handler (connection)
   1483   (add-fd-handler (connection-socket-io connection)
   1484                   (lambda () (handle-requests connection t)))
   1485   (setf (sconn.saved-sigint-handler connection)
   1486         (install-sigint-handler
   1487          (lambda ()
   1488            (invoke-or-queue-interrupt
   1489             (lambda () (dispatch-interrupt-event connection))))))
   1490   (handle-requests connection t))
   1491 
   1492 (defun dispatch-interrupt-event (connection)
   1493   (with-connection (connection)
   1494     (dispatch-event connection `(:emacs-interrupt ,(current-thread-id)))))
   1495 
   1496 (defun deinstall-fd-handler (connection)
   1497   (log-event "deinstall-fd-handler~%")
   1498   (remove-fd-handlers (connection-socket-io connection))
   1499   (install-sigint-handler (sconn.saved-sigint-handler connection)))
   1500 
   1501 ;;;;;; Simple sequential IO
   1502 
   1503 (defun simple-serve-requests (connection)
   1504   (unwind-protect
   1505        (with-connection (connection)
   1506          (call-with-user-break-handler
   1507           (lambda ()
   1508             (invoke-or-queue-interrupt
   1509              (lambda () (dispatch-interrupt-event connection))))
   1510           (lambda ()
   1511             (with-simple-restart (close-connection "Close SLY connection.")
   1512               (let* ((stdin (real-input-stream *standard-input*))
   1513                      (*standard-input* (make-repl-input-stream connection
   1514                                                                stdin)))
   1515                 (tagbody toplevel
   1516                    (with-top-level-restart (connection (go toplevel))
   1517                      (simple-repl))))))))
   1518     (close-connection connection nil (safe-backtrace))))
   1519 
   1520 ;; this is signalled when our custom stream thinks the end-of-file is reached.
   1521 ;; (not when the end-of-file on the socket is reached)
   1522 (define-condition end-of-repl-input (end-of-file) ())
   1523 
   1524 (defun simple-repl ()
   1525   (loop
   1526    (format t "~a> " (package-string-for-prompt *package*))
   1527    (force-output)
   1528    (let ((form (handler-case (read)
   1529                  (end-of-repl-input () (return)))))
   1530      (let* ((- form)
   1531             (values (multiple-value-list (eval form))))
   1532        (setq *** **  ** *  * (car values)
   1533              /// //  // /  / values
   1534              +++ ++  ++ +  + form)
   1535        (cond ((null values) (format t "; No values~&"))
   1536              (t (mapc (lambda (v) (format t "~s~&" v)) values)))))))
   1537 
   1538 (defun make-repl-input-stream (connection stdin)
   1539   (make-input-stream
   1540    (lambda () (repl-input-stream-read connection stdin))))
   1541 
   1542 (defun repl-input-stream-read (connection stdin)
   1543   (loop
   1544    (let* ((socket (connection-socket-io connection))
   1545           (inputs (list socket stdin))
   1546           (ready (wait-for-input inputs)))
   1547      (cond ((eq ready :interrupt)
   1548             (check-sly-interrupts))
   1549            ((member socket ready)
   1550             ;; A Sly request from Emacs is pending; make sure to
   1551             ;; redirect IO to the REPL buffer.
   1552             (with-simple-restart (process-input "Continue reading input.")
   1553               (let ((*sly-db-quit-restart* (find-restart 'process-input)))
   1554                 (with-default-listener (connection)
   1555                   (handle-requests connection t)))))
   1556            ((member stdin ready)
   1557             ;; User typed something into the  *inferior-lisp* buffer,
   1558             ;; so do not redirect.
   1559             (return (read-non-blocking stdin)))
   1560            (t (assert (null ready)))))))
   1561 
   1562 (defun read-non-blocking (stream)
   1563   (with-output-to-string (str)
   1564     (handler-case
   1565         (loop (let ((c (read-char-no-hang stream)))
   1566                 (unless c (return))
   1567                 (write-char c str)))
   1568       (end-of-file () (error 'end-of-repl-input :stream stream)))))
   1569 
   1570 
   1571 
   1572 (defvar *sly-features* nil
   1573   "The feature list that has been sent to Emacs.")
   1574 
   1575 (defun send-oob-to-emacs (object)
   1576   (send-to-emacs object))
   1577 
   1578 (defun force-user-output ()
   1579   (with-default-listener (*emacs-connection*)
   1580     (force-output *standard-output*)))
   1581 
   1582 (add-hook *pre-reply-hook* 'force-user-output)
   1583 
   1584 (defun clear-user-input  ()
   1585   (with-default-listener (*emacs-connection*)
   1586     (clear-input *standard-input*)))
   1587 
   1588 ;; FIXME: not thread safe.
   1589 (defvar *tag-counter* 0)
   1590 
   1591 (defun make-tag ()
   1592   (setq *tag-counter* (mod (1+ *tag-counter*) (expt 2 22))))
   1593 
   1594 (defun y-or-n-p-in-emacs (format-string &rest arguments)
   1595   "Like y-or-n-p, but ask in the Emacs minibuffer."
   1596   (let ((tag (make-tag))
   1597         (question (apply #'format nil format-string arguments)))
   1598     (force-output)
   1599     (send-to-emacs `(:y-or-n-p ,(current-thread-id) ,tag ,question))
   1600     (third (wait-for-event `(:emacs-return ,tag result)))))
   1601 
   1602 (defun read-from-minibuffer-in-emacs (prompt &optional initial-value)
   1603   "Ask user a question in Emacs' minibuffer. Returns \"\" when user
   1604 entered nothing, returns NIL when user pressed C-g."
   1605   (check-type prompt string) (check-type initial-value (or null string))
   1606   (let ((tag (make-tag)))
   1607     (force-output)
   1608     (send-to-emacs `(:read-from-minibuffer ,(current-thread-id) ,tag
   1609                                            ,prompt ,initial-value))
   1610     (third (wait-for-event `(:emacs-return ,tag result)))))
   1611 
   1612 (defun process-form-for-emacs (form)
   1613   "Returns a string which emacs will read as equivalent to
   1614 FORM. FORM can contain lists, strings, characters, symbols and
   1615 numbers.
   1616 
   1617 Characters are converted emacs' ?<char> notaion, strings are left
   1618 as they are (except for espacing any nested \" chars, numbers are
   1619 printed in base 10 and symbols are printed as their symbol-name
   1620 converted to lower case."
   1621   (etypecase form
   1622     (string (format nil "~S" form))
   1623     (cons (format nil "(~A . ~A)"
   1624                   (process-form-for-emacs (car form))
   1625                   (process-form-for-emacs (cdr form))))
   1626     (character (format nil "?~C" form))
   1627     (symbol (concatenate 'string (when (eq (symbol-package form)
   1628                                            #.(find-package "KEYWORD"))
   1629                                    ":")
   1630                          (string-downcase (symbol-name form))))
   1631     (number (let ((*print-base* 10))
   1632               (princ-to-string form)))))
   1633 
   1634 (defun eval-in-emacs (form &optional nowait)
   1635   "Eval FORM in Emacs.
   1636 `sly-enable-evaluate-in-emacs' should be set to T on the Emacs side."
   1637   (cond (nowait
   1638          (send-to-emacs `(:eval-no-wait ,(process-form-for-emacs form))))
   1639         (t
   1640          (force-output)
   1641          (let ((tag (make-tag)))
   1642 	   (send-to-emacs `(:eval ,(current-thread-id) ,tag
   1643 				  ,(process-form-for-emacs form)))
   1644 	   (let ((value (caddr (wait-for-event `(:emacs-return ,tag result)))))
   1645 	     (destructure-case value
   1646 	       ((:ok value) value)
   1647                ((:error kind . data) (error "~a: ~{~a~}" kind data))
   1648 	       ((:abort) (abort))))))))
   1649 
   1650 (defun sly-version-string ()
   1651   "Return a string identifying the SLY version.
   1652 Return nil if nothing appropriate is available."
   1653   (let ((this-file #.(or *compile-file-truename* *load-truename*)))
   1654     (with-open-file (s (make-pathname :name "sly" :type "el"
   1655                                       :directory (butlast
   1656                                                   (pathname-directory this-file)
   1657                                                   1)
   1658                                       :defaults this-file))
   1659       (let ((seq (make-array 200 :element-type 'character :initial-element #\null)))
   1660         (read-sequence seq s :end 200)
   1661         (let* ((beg (search ";; Version:" seq))
   1662                (end (position #\NewLine seq :start beg))
   1663                (middle (position #\Space seq :from-end t :end end)))
   1664           (subseq seq (1+ middle) end))))))
   1665 
   1666 (defvar *slynk-wire-protocol-version* (ignore-errors (sly-version-string))
   1667   "The version of the slynk/sly communication protocol.")
   1668 
   1669 (defslyfun connection-info ()
   1670   "Return a key-value list of the form:
   1671 \(&key PID STYLE LISP-IMPLEMENTATION MACHINE FEATURES PACKAGE VERSION)
   1672 PID: is the process-id of Lisp process (or nil, depending on the STYLE)
   1673 STYLE: the communication style
   1674 LISP-IMPLEMENTATION: a list (&key TYPE NAME VERSION PROGRAM)
   1675 FEATURES: a list of keywords
   1676 PACKAGE: a list (&key NAME PROMPT)
   1677 VERSION: the protocol version"
   1678   (let ((c *emacs-connection*))
   1679     (setq *sly-features* *features*)
   1680     `(:pid ,(getpid) :style ,(connection-communication-style c)
   1681       :encoding (:coding-systems
   1682                  ,(loop for cs in '("utf-8-unix" "iso-latin-1-unix")
   1683                         when (find-external-format cs) collect cs))
   1684       :lisp-implementation (:type ,(lisp-implementation-type)
   1685                             :name ,(lisp-implementation-type-name)
   1686                             :version ,(lisp-implementation-version)
   1687                             :program ,(lisp-implementation-program))
   1688       :machine (:instance ,(machine-instance)
   1689                :type ,(machine-type)
   1690                :version ,(machine-version))
   1691       :features ,(features-for-emacs)
   1692       :modules ,*modules*
   1693       :package (:name ,(package-name *package*)
   1694                :prompt ,(package-string-for-prompt *package*))
   1695       :version ,*slynk-wire-protocol-version*)))
   1696 
   1697 (defun debug-on-slynk-error ()
   1698   (assert (eq *debug-on-slynk-protocol-error* *debug-slynk-backend*))
   1699   *debug-on-slynk-protocol-error*)
   1700 
   1701 (defun (setf debug-on-slynk-error) (new-value)
   1702   (setf *debug-on-slynk-protocol-error* new-value)
   1703   (setf *debug-slynk-backend* new-value))
   1704 
   1705 (defslyfun toggle-debug-on-slynk-error ()
   1706   (setf (debug-on-slynk-error) (not (debug-on-slynk-error))))
   1707 
   1708 
   1709 ;;;; Reading and printing
   1710 
   1711 (defvar-unbound *buffer-package*
   1712     "Package corresponding to sly-buffer-package.
   1713 
   1714 EVAL-FOR-EMACS binds *buffer-package*.  Strings originating from a sly
   1715 buffer are best read in this package.  See also FROM-STRING and TO-STRING.")
   1716 
   1717 (defvar-unbound *buffer-readtable*
   1718     "Readtable associated with the current buffer")
   1719 
   1720 (defmacro with-buffer-syntax ((&optional package-designator
   1721                                          readtable)
   1722                               &body body)
   1723   "Conceptually execute BODY inside a SLY Lisp buffer.
   1724 
   1725 Execute BODY with appropriate *PACKAGE* and *READTABLE* bindings.
   1726 
   1727 PACKAGE-DESIGNATOR, if non-NIL, is anything remotely designating a
   1728 package.  READTABLE, if non-NIL, must verify CL:READTABLEP.
   1729 
   1730 READTABLE defaults to *BUFFER-READTABLE* as set by
   1731 GUESS-BUFFER-READTABLE, which in turn uses a mapping in
   1732 *READTABLE-ALIST* as indexed by *BUFFER-PACKAGE*, and *not*
   1733 PACKAGE-DESIGNATOR.
   1734 
   1735 This should be used for code that is conceptionally executed in an
   1736 Emacs buffer."
   1737   `(call-with-buffer-syntax ,package-designator ,readtable (lambda () ,@body)))
   1738 
   1739 (defun call-with-buffer-syntax (package readtable fun)
   1740   (let ((*package* (if package
   1741                        (guess-buffer-package package)
   1742                        *buffer-package*))
   1743         (*buffer-readtable* (or (and (readtablep readtable)
   1744                                      readtable)
   1745                                 *buffer-readtable*)))
   1746     ;; Don't shadow *readtable* unnecessarily because that prevents
   1747     ;; the user from assigning to it.
   1748     (if (eq *readtable* *buffer-readtable*)
   1749         (call-with-syntax-hooks fun)
   1750         (let ((*readtable* *buffer-readtable*))
   1751           (call-with-syntax-hooks fun)))))
   1752 
   1753 (defmacro without-printing-errors ((&key object stream
   1754                                         (msg "<<error printing object>>"))
   1755                                   &body body)
   1756   ;; JT: Careful when calling this, make sure STREAM, if provided, is
   1757   ;; a symbol that alwyas designates a non-nil stream.  See gh#287.
   1758   "Catches errors during evaluation of BODY and prints MSG instead."
   1759   `(handler-case (progn ,@body)
   1760      (serious-condition ()
   1761        ,(cond ((and stream object)
   1762                (let ((gstream (gensym "STREAM+")))
   1763                  `(let ((,gstream ,stream))
   1764                     (print-unreadable-object (,object ,gstream :type t
   1765                                                       :identity t)
   1766                       (write-string ,msg ,gstream)))))
   1767               (stream
   1768                `(write-string ,msg ,stream))
   1769               (object
   1770                `(with-output-to-string (s)
   1771                   (print-unreadable-object (,object s :type t :identity t)
   1772                     (write-string ,msg  s))))
   1773               (t msg)))))
   1774 
   1775 (defun to-string (object)
   1776   "Write OBJECT in the *BUFFER-PACKAGE*.
   1777 The result may not be readable. Handles problems with PRINT-OBJECT methods
   1778 gracefully."
   1779   (with-buffer-syntax ()
   1780     (let ((*print-readably* nil))
   1781       (without-printing-errors (:object object :stream nil)
   1782         (prin1-to-string object)))))
   1783 
   1784 (defun from-string (string)
   1785   "Read string in the *BUFFER-PACKAGE*"
   1786   (with-buffer-syntax ()
   1787     (let ((*read-suppress* nil))
   1788       (values (read-from-string string)))))
   1789 
   1790 (defun parse-string (string package)
   1791   "Read STRING in PACKAGE."
   1792   (with-buffer-syntax (package)
   1793     (let ((*read-suppress* nil))
   1794       (read-from-string string))))
   1795 
   1796 ;; FIXME: deal with #\| etc.  hard to do portably.
   1797 (defun tokenize-symbol (string)
   1798   "STRING is interpreted as the string representation of a symbol
   1799 and is tokenized accordingly. The result is returned in three
   1800 values: The package identifier part, the actual symbol identifier
   1801 part, and a flag if the STRING represents a symbol that is
   1802 internal to the package identifier part. (Notice that the flag is
   1803 also true with an empty package identifier part, as the STRING is
   1804 considered to represent a symbol internal to some current package.)"
   1805   (let ((package (let ((pos (position #\: string)))
   1806                    (if pos (subseq string 0 pos) nil)))
   1807         (symbol (let ((pos (position #\: string :from-end t)))
   1808                   (if pos (subseq string (1+ pos)) string)))
   1809         (internp (not (= (count #\: string) 1))))
   1810     (values symbol package internp)))
   1811 
   1812 (defun tokenize-symbol-thoroughly (string)
   1813   "This version of TOKENIZE-SYMBOL handles escape characters."
   1814   (let ((package nil)
   1815         (token (make-array (length string) :element-type 'character
   1816                                            :fill-pointer 0))
   1817         (backslash nil)
   1818         (vertical nil)
   1819         (internp nil)
   1820         (caser (char-casifier string)))
   1821     (loop for char across string do
   1822           (cond
   1823             (backslash
   1824              (vector-push-extend char token)
   1825              (setq backslash nil))
   1826             ((char= char #\\) ; Quotes next character, even within |...|
   1827              (setq backslash t))
   1828             ((char= char #\|)
   1829              (setq vertical (not vertical)))
   1830             (vertical
   1831              (vector-push-extend char token))
   1832             ((char= char #\:)
   1833              (cond ((and package internp)
   1834                     (return-from tokenize-symbol-thoroughly))
   1835                    (package
   1836                     (setq internp t))
   1837                    (t
   1838                     (setq package token
   1839                           token (make-array (length string)
   1840                                             :element-type 'character
   1841                                             :fill-pointer 0)))))
   1842             (t
   1843              (vector-push-extend (funcall caser char) token))))
   1844     (unless vertical
   1845           (values token package (or (not package) internp)))))
   1846 
   1847 (defun untokenize-symbol (package-name internal-p symbol-name)
   1848   "The inverse of TOKENIZE-SYMBOL.
   1849 
   1850   (untokenize-symbol \"quux\" nil \"foo\") ==> \"quux:foo\"
   1851   (untokenize-symbol \"quux\" t \"foo\")   ==> \"quux::foo\"
   1852   (untokenize-symbol nil nil \"foo\")    ==> \"foo\"
   1853 "
   1854   (cond ((not package-name) 	symbol-name)
   1855         (internal-p 		(cat package-name "::" symbol-name))
   1856         (t 			(cat package-name ":" symbol-name))))
   1857 
   1858 (defun char-casifier (string)
   1859   "Return a function which converts characters in STRING according to `readtable-case'."
   1860   (ecase (readtable-case *readtable*)
   1861     (:preserve #'identity)
   1862     (:upcase   #'char-upcase)
   1863     (:downcase #'char-downcase)
   1864     ;; :invert only inverts the case if every character of a token is the same
   1865     ;; case, otherwise it acts like :preserve.
   1866     (:invert (let ((upper (count-if #'upper-case-p string)))
   1867                (cond ((= upper 0) #'char-upcase)
   1868                      ((= upper (length string)) #'char-downcase)
   1869                      (t #'identity))))))
   1870 
   1871 
   1872 (defun find-symbol-with-status (symbol-name status
   1873                                 &optional (package *package*))
   1874   (multiple-value-bind (symbol flag) (find-symbol symbol-name package)
   1875     (if (and flag (eq flag status))
   1876         (values symbol flag)
   1877         (values nil nil))))
   1878 
   1879 (defun parse-symbol (string &optional (package *package*))
   1880   "Find the symbol named STRING.
   1881 Return the symbol and a flag indicating whether the symbols was found."
   1882   (multiple-value-bind (sname pname internalp)
   1883       (tokenize-symbol-thoroughly string)
   1884     (when sname
   1885      (let ((package (cond ((string= pname "") +keyword-package+)
   1886                           (pname              (find-package pname))
   1887                           (t                  package))))
   1888        (if package
   1889            (multiple-value-bind (symbol flag)
   1890                (if internalp
   1891                    (find-symbol sname package)
   1892                    (find-symbol-with-status sname ':external package))
   1893              (values symbol flag sname package))
   1894            (values nil nil nil nil))))))
   1895 
   1896 (defun parse-symbol-or-lose (string &optional (package *package*))
   1897   (multiple-value-bind (symbol status) (parse-symbol string package)
   1898     (if status
   1899         (values symbol status)
   1900         (error "Unknown symbol: ~A [in ~A]" string package))))
   1901 
   1902 (defun parse-package (string)
   1903   "Find the package named STRING.
   1904 Return the package or nil."
   1905   ;; STRING comes usually from a (in-package STRING) form.
   1906   (ignore-errors
   1907     (find-package (let ((*package* *slynk-io-package*))
   1908                     (read-from-string string)))))
   1909 
   1910 (defun unparse-name (string)
   1911   "Print the name STRING according to the current printer settings."
   1912   ;; this is intended for package or symbol names
   1913   (subseq (prin1-to-string (make-symbol string)) 2))
   1914 
   1915 (defun guess-package (string)
   1916   "Guess which package corresponds to STRING.
   1917 Return nil if no package matches."
   1918   (when string
   1919     (or (find-package string)
   1920         (parse-package string)
   1921         (if (find #\! string)           ; for SBCL
   1922             (guess-package (substitute #\- #\! string))))))
   1923 
   1924 (defvar *readtable-alist* (default-readtable-alist)
   1925   "An alist mapping package names to readtables.")
   1926 
   1927 (defun guess-buffer-readtable (package-name)
   1928   (let ((package (guess-package package-name)))
   1929     (or (and package
   1930              (cdr (assoc (package-name package) *readtable-alist*
   1931                          :test #'string=)))
   1932         *readtable*)))
   1933 
   1934 
   1935 ;;;; Evaluation
   1936 
   1937 (defvar *pending-continuations* '()
   1938   "List of continuations for Emacs. (thread local)")
   1939 
   1940 (defun guess-buffer-package (string)
   1941   "Return a package for STRING.
   1942 Fall back to the current if no such package exists."
   1943   (or (and string (guess-package string))
   1944       *package*))
   1945 
   1946 (defvar *eval-for-emacs-wrappers* nil
   1947   "List of functions for fine-grained control over form evaluation.
   1948 Each element must be a function taking an arbitrary number of
   1949 arguments, the first of which is a function of no arguments, call it
   1950 IN-FUNCTION, while the remaining are bound to the EXTRA-REX-OPTIONS
   1951 parameter of EVAL-FOR-EMACS.  Every function *must* return another
   1952 function of no arguments, call it OUT-FUNCTION, that, when called,
   1953 *must* call IN-FUNCTION in whatever dynamic environment it sees fit.
   1954 
   1955 Slynk will go through the elements of this variable in order, passing
   1956 a function that evaluates the form coming from Emacs to the first
   1957 element until it collects the result of the last, which is finally
   1958 called with no arguments.
   1959 
   1960 Be careful when changing this variable since you may mess very basic
   1961 functionality of your Slynk, including the ability to correct any
   1962 errors you make.")
   1963 
   1964 (defun eval-for-emacs (form buffer-package id &rest extra-rex-options)
   1965   "Bind *BUFFER-PACKAGE* to BUFFER-PACKAGE and evaluate FORM.
   1966 Return the result to the continuation ID.  Errors are trapped and
   1967 invoke our debugger.  EXTRA-REX-OPTIONS are passed to the functions of
   1968 *EVAL-FOR-EMACS-WRAPPERS*, which see."
   1969   (let (ok result condition)
   1970     (unwind-protect
   1971          (let ((*buffer-package* (guess-buffer-package buffer-package))
   1972                (*buffer-readtable* (guess-buffer-readtable buffer-package))
   1973                (*pending-continuations* (cons id *pending-continuations*)))
   1974            (check-type *buffer-package* package)
   1975            (check-type *buffer-readtable* readtable)
   1976            (handler-bind ((t (lambda (c) (setf condition c))))
   1977              (setq result (with-sly-interrupts
   1978                             (flet ((eval-it ()
   1979                                      ;; APPLY would be cleaner than EVAL.
   1980                                      ;; (setq result (apply (car form) (cdr form)))
   1981                                      (eval form)))
   1982                               ;; Honour *EVAL-FOR-EMACS-WRAPPERS*
   1983                               ;; 
   1984                               (loop for lambda = #'eval-it then
   1985                                                            (handler-case
   1986                                                                (apply wrapper lambda extra-rex-options)
   1987                                                              (error (e)
   1988                                                                (warn "~s ignoring wrapper ~a (~a)"
   1989                                                                      'eval-for-emacs wrapper e)
   1990                                                                lambda))
   1991                                     for wrapper in *eval-for-emacs-wrappers*
   1992                                     finally (return (funcall lambda)))))))
   1993            (run-hook *pre-reply-hook*)
   1994            (setq ok t))
   1995       (send-to-emacs `(:return ,(current-thread)
   1996                                ,(if ok
   1997                                     `(:ok ,result)
   1998                                     `(:abort ,(prin1-to-string condition)))
   1999                                ,id)))))
   2000 
   2001 (defun format-integer-length (i) (format nil "~a bit~:p" (integer-length i)))
   2002 (defun format-integer-as-hex (i)
   2003   (unless (or (minusp i) (> (integer-length i) 64)) (format nil "#x~X" i)))
   2004 (defun format-integer-as-octal (i)
   2005   (unless (or (minusp i) (> (integer-length i) 8)) (format nil "#o~O" i)))
   2006 (defun format-integer-as-binary (i) -128
   2007   (unless (or (minusp i) (> (integer-length i) 8)) (format nil "#b~B" i)))
   2008 (defun format-ratio-as-float (r) (ignore-errors (format nil "~f" r)))
   2009 (defun format-as-percentage-maybe (f) (when (< 0 (abs f) 2) (format nil "~2,'0d%" (* f 100))))
   2010 
   2011 (defparameter *echo-number-alist*
   2012   '((integer . (format-integer-length format-integer-as-hex format-integer-as-octal format-integer-as-binary))
   2013     (ratio . (format-ratio-as-float format-as-percentage-maybe))
   2014     (float . (format-as-percentage-maybe)))
   2015   "Alist of functions used for presenting numbers in the echo area.
   2016 
   2017 Each element takes the form (TYPE . FUNCTIONS), where TYPE is a type
   2018 designator and FUNCTIONS is a list of function designators for
   2019 displaying that number in SLY. Each function takes the number as a
   2020 single argument and returns a string, or nil, if that particular
   2021 representation is to be disregarded.
   2022 
   2023 Additionally if a given function chooses to return t as its optional
   2024 second value, then all the remaining functions following it in the
   2025 list are disregarded.")
   2026 
   2027 (defparameter *present-number-alist* nil
   2028   "Alist of functions used for presenting numbers the REPL.
   2029 
   2030 This is an \"override\". If nil the (the alist is empty) the value of
   2031 *ECHO-NUMBER-ALIST* is used, otherwise the structure is exactly the
   2032 same as that variable.")
   2033 
   2034 (defun present-number-considering-alist (number alist)
   2035   (let* ((functions (cdr (assoc number alist :test #'typep)))
   2036          (extra-presentations
   2037            (loop for fn in functions
   2038                  for (display skip)
   2039                    = (multiple-value-list
   2040                       (handler-case
   2041                           (funcall fn number)
   2042                         (error (e)
   2043                           (declare (ignore e))
   2044                           "<error echoing>")))
   2045                  when display collect it
   2046                    until skip)))
   2047     (if extra-presentations
   2048         (format nil "~A (~{~a~^, ~})"
   2049                 number extra-presentations)
   2050         (format nil "~A" number))))
   2051 
   2052 (defun echo-for-emacs (values &optional (fn #'slynk-pprint))
   2053   "Format VALUES in a way suitable to be echoed in the SLY client.
   2054 May insert newlines between each of VALUES.  Considers
   2055 *ECHO-NUMBER-ALIST*."
   2056   (let ((*print-readably* nil))
   2057     (cond ((null values) "; No value")
   2058           ((and (numberp (car values))
   2059                 (null (cdr values)))
   2060            (present-number-considering-alist (car values) *echo-number-alist*))
   2061           (t
   2062            (let ((strings (loop for v in values
   2063                                 collect (funcall fn v))))
   2064              (if (some #'(lambda (s) (find #\Newline s))
   2065                        strings)
   2066                  (format nil "~{~a~^~%~}" strings)
   2067                  (format nil "~{~a~^, ~}" strings)))))))
   2068 
   2069 (defun present-for-emacs (value &optional (fn #'slynk-pprint))
   2070   "Format VALUE in a way suitable to be displayed in the SLY client.
   2071 FN is only used if value is not a number"
   2072   (if (numberp value)
   2073       (present-number-considering-alist value (or *present-number-alist*
   2074                                                   *echo-number-alist*))
   2075       (funcall fn value)))
   2076 
   2077 (defslyfun interactive-eval (string)
   2078   (with-buffer-syntax ()
   2079     (with-retry-restart (:msg "Retry SLY interactive evaluation request.")
   2080       (let ((values (multiple-value-list (eval (from-string string)))))
   2081         (finish-output)
   2082         (echo-for-emacs values)))))
   2083 
   2084 (defslyfun eval-and-grab-output (string)
   2085   (with-buffer-syntax ()
   2086     (with-retry-restart (:msg "Retry SLY evaluation request.")
   2087       (let* ((s (make-string-output-stream))
   2088              (*standard-output* s)
   2089              (values (multiple-value-list (eval (from-string string)))))
   2090         (list (get-output-stream-string s)
   2091               (echo-for-emacs values))))))
   2092 
   2093 (defun eval-region (string)
   2094   "Evaluate STRING.
   2095 Return the results of the last form as a list and as secondary value the
   2096 last form."
   2097   (with-input-from-string (stream string)
   2098     (let (- values)
   2099       (loop
   2100        (let ((form (read stream nil stream)))
   2101          (when (eq form stream)
   2102            (finish-output)
   2103            (return (values values -)))
   2104          (setq - form)
   2105          (setq values (multiple-value-list (eval form)))
   2106          (finish-output))))))
   2107 
   2108 (defslyfun interactive-eval-region (string)
   2109   (with-buffer-syntax ()
   2110     (with-retry-restart (:msg "Retry SLY interactive evaluation request.")
   2111       (echo-for-emacs (eval-region string)))))
   2112 
   2113 (defslyfun re-evaluate-defvar (form)
   2114   (with-buffer-syntax ()
   2115     (with-retry-restart (:msg "Retry SLY evaluation request.")
   2116       (let ((form (read-from-string form)))
   2117         (destructuring-bind (dv name &optional value doc) form
   2118           (declare (ignore value doc))
   2119           (assert (eq dv 'defvar))
   2120           (makunbound name)
   2121           (prin1-to-string (eval form)))))))
   2122 
   2123 (defvar-unbound *string-elision-length*
   2124   "Maximum length of a sring before elision by SLYNK-PPRINT.")
   2125 
   2126 (defparameter *slynk-pprint-bindings*
   2127   `((*print-pretty*           . t)
   2128     (*print-level*            . nil)
   2129     (*print-length*           . nil)
   2130     (*string-elision-length*  . 200)
   2131     (*print-circle*           . nil)
   2132     (*print-gensym*           . t)
   2133     (*print-readably*         . nil))
   2134   "A list of variables bindings during pretty printing.
   2135 Used by pprint-eval.")
   2136 
   2137 (defun slynk-pprint (object &key (stream nil))
   2138   "Pretty print OBJECT to STREAM using *SLYNK-PPRINT-BINDINGS*.
   2139 If STREAM is nil, use a string"
   2140   (with-bindings *slynk-pprint-bindings*
   2141     ;; a failsafe for *PRINT-LENGTH* and *PRINT-LEVEL*: if they're NIL
   2142     ;; and *PRINT-CIRCLE* is also nil we could be in trouble printing
   2143     ;; recursive structures.
   2144     ;;
   2145     (let ((*print-length* (or *print-length*
   2146                               (and (not *print-circle*) 512)))
   2147           (*print-level* (or *print-level*
   2148                               (and (not *print-circle*) 20))))
   2149       (flet ((write-it (s)
   2150                (cond ((and *string-elision-length*
   2151                            (stringp object)
   2152                            (> (length object) *string-elision-length*))
   2153                       (format s "\"~a...[sly-elided string of length ~a]\""
   2154                               (subseq object 0 *string-elision-length*)
   2155                               (length object)))
   2156                      (t
   2157                       (write object :stream s :pretty t :escape t)))))
   2158         (if stream
   2159             (without-printing-errors (:object object :stream stream)
   2160               (write-it stream))
   2161             (without-printing-errors (:object object)
   2162               (with-output-to-string (s) (write-it s))))))))
   2163 
   2164 (defun slynk-pprint-values (values &key (stream nil))
   2165   "Pretty print each of VALUES to STREAM using *SLYNK-PPRINT-BINDINGS*.
   2166 Separated by a newline. If no values indicate that in a comment.
   2167 If STREAM is nil, use a string"
   2168   (labels ((print-one (object s)
   2169              (let ((*slynk-pprint-bindings* nil))
   2170                (slynk-pprint object :stream s)))
   2171            (print-all (s)
   2172              (loop for o in values
   2173                    do (print-one o s)
   2174                       (terpri))))
   2175     (with-bindings *slynk-pprint-bindings*
   2176       (cond ((null values)
   2177              (format stream "; No value"))
   2178             (t
   2179              (if stream
   2180                  (print-all stream)
   2181                  (with-output-to-string (s)
   2182                    (print-all s))))))))
   2183 
   2184 (defun slynk-pprint-to-line (object)
   2185   "Print OBJECT to a single line string and return it."
   2186   (let ((*slynk-pprint-bindings*
   2187           `((*print-lines* . 1)
   2188             (*print-right-margin* . 512)
   2189             ,@*slynk-pprint-bindings*)))
   2190     (substitute #\Space #\Newline (slynk-pprint object :stream nil))))
   2191 
   2192 (defslyfun pprint-eval (string)
   2193   (with-buffer-syntax ()
   2194     (let* ((s (make-string-output-stream))
   2195            (values
   2196             (let ((*standard-output* s)
   2197                   (*trace-output* s))
   2198               (multiple-value-list (eval (read-from-string string))))))
   2199       (cat (get-output-stream-string s)
   2200            (slynk-pprint-values values)))))
   2201 
   2202 (defslyfun set-package (name)
   2203   "Set *package* to the package named NAME.
   2204 Return the full package-name and the string to use in the prompt."
   2205   (let ((p (guess-package name)))
   2206     (assert (packagep p) nil "Package ~a doesn't exist." name)
   2207     (setq *package* p)
   2208     (list (package-name p) (package-string-for-prompt p))))
   2209 
   2210 (defun cat (&rest strings)
   2211   "Concatenate all arguments and make the result a string."
   2212   (with-output-to-string (out)
   2213     (dolist (s strings)
   2214       (etypecase s
   2215         (string (write-string s out))
   2216         (character (write-char s out))))))
   2217 
   2218 (defun truncate-string (string width &optional ellipsis)
   2219   (let ((len (length string)))
   2220     (cond ((< len width) string)
   2221           (ellipsis (cat (subseq string 0 width) ellipsis))
   2222           (t (subseq string 0 width)))))
   2223 
   2224 (defun call/truncated-output-to-string (length function
   2225                                         &optional (ellipsis ".."))
   2226   "Call FUNCTION with a new stream, return the output written to the stream.
   2227 If FUNCTION tries to write more than LENGTH characters, it will be
   2228 aborted and return immediately with the output written so far."
   2229   (let ((buffer (make-string (+ length (length ellipsis))))
   2230         (fill-pointer 0))
   2231     (block buffer-full
   2232       (flet ((write-output (string)
   2233                (let* ((free (- length fill-pointer))
   2234                       (count (min free (length string))))
   2235                  (replace buffer string :start1 fill-pointer :end2 count)
   2236                  (incf fill-pointer count)
   2237                  (when (> (length string) free)
   2238                    (replace buffer ellipsis :start1 fill-pointer)
   2239                    (return-from buffer-full buffer)))))
   2240         (let ((stream (make-output-stream #'write-output)))
   2241           (funcall function stream)
   2242           (finish-output stream)
   2243           (subseq buffer 0 fill-pointer))))))
   2244 
   2245 (defmacro with-string-stream ((var &key length bindings)
   2246                               &body body)
   2247   (cond ((and (not bindings) (not length))
   2248          `(with-output-to-string (,var) . ,body))
   2249         ((not bindings)
   2250          `(call/truncated-output-to-string
   2251            ,length (lambda (,var) . ,body)))
   2252         (t
   2253          `(with-bindings ,bindings
   2254             (with-string-stream (,var :length ,length)
   2255               . ,body)))))
   2256 
   2257 (defun escape-string (string stream &key length (map '((#\" . "\\\"")
   2258                                                        (#\\ . "\\\\"))))
   2259   "Write STRING to STREAM surronded by double-quotes.
   2260 LENGTH -- if non-nil truncate output after LENGTH chars.
   2261 MAP -- rewrite the chars in STRING according to this alist."
   2262   (let ((limit (or length array-dimension-limit)))
   2263     (write-char #\" stream)
   2264     (loop for c across string
   2265           for i from 0 do
   2266           (when (= i limit)
   2267             (write-string "..." stream)
   2268             (return))
   2269           (let ((probe (assoc c map)))
   2270             (cond (probe (write-string (cdr probe) stream))
   2271                   (t (write-char c stream)))))
   2272     (write-char #\" stream)))
   2273 
   2274 
   2275 ;;;; Prompt
   2276 
   2277 ;; FIXME: do we really need 45 lines of code just to figure out the
   2278 ;; prompt?
   2279 
   2280 (defvar *canonical-package-nicknames*
   2281   `((:common-lisp-user . :cl-user))
   2282   "Canonical package names to use instead of shortest name/nickname.")
   2283   
   2284 (defvar *auto-abbreviate-dotted-packages* t
   2285   "Abbreviate dotted package names to their last component if T.")
   2286 
   2287 (defun package-string-for-prompt (package)
   2288   "Return the shortest nickname (or canonical name) of PACKAGE."
   2289   (unparse-name
   2290    (or (canonical-package-nickname package)
   2291        (auto-abbreviated-package-name package)
   2292        (shortest-package-nickname package))))
   2293 
   2294 (defun canonical-package-nickname (package)
   2295   "Return the canonical package nickname, if any, of PACKAGE."
   2296   (let ((name (cdr (assoc (package-name package) *canonical-package-nicknames*
   2297                           :test #'string=))))
   2298     (and name (string name))))
   2299 
   2300 (defun auto-abbreviated-package-name (package)
   2301   "Return an abbreviated 'name' for PACKAGE.
   2302 
   2303 N.B. this is not an actual package name or nickname."
   2304   (when *auto-abbreviate-dotted-packages*
   2305     (loop with package-name = (package-name package)
   2306           with offset = nil
   2307           do (let ((last-dot-pos (position #\. package-name :end offset
   2308                                            :from-end t)))
   2309                (unless last-dot-pos
   2310                  (return nil))
   2311                ;; If a dot chunk contains only numbers, that chunk most
   2312                ;; likely represents a version number; so we collect the
   2313                ;; next chunks, too, until we find one with meat.
   2314                (let ((name (subseq package-name (1+ last-dot-pos) offset)))
   2315                  (if (notevery #'digit-char-p name)
   2316                      (return (subseq package-name (1+ last-dot-pos)))
   2317                      (setq offset last-dot-pos)))))))
   2318 
   2319 (defun shortest-package-nickname (package)
   2320   "Return the shortest nickname of PACKAGE."
   2321   (loop for name in (cons (package-name package) (package-nicknames package))
   2322         for shortest = name then (if (< (length name) (length shortest))
   2323                                    name
   2324                                    shortest)
   2325               finally (return shortest)))
   2326 
   2327 
   2328 
   2329 (defslyfun ed-in-emacs (&optional what)
   2330   "Edit WHAT in Emacs.
   2331 
   2332 WHAT can be:
   2333   A pathname or a string,
   2334   A list (PATHNAME-OR-STRING &key LINE COLUMN POSITION),
   2335   A function name (symbol or cons),
   2336   NIL. "
   2337   (flet ((canonicalize-filename (filename)
   2338            (pathname-to-filename (or (probe-file filename) filename))))
   2339     (let ((target
   2340            (etypecase what
   2341              (null nil)
   2342              ((or string pathname)
   2343               `(:filename ,(canonicalize-filename what)))
   2344              ((cons (or string pathname) *)
   2345               `(:filename ,(canonicalize-filename (car what)) ,@(cdr what)))
   2346              ((or symbol cons)
   2347               `(:function-name ,(prin1-to-string what))))))
   2348       (cond (*emacs-connection* (send-oob-to-emacs `(:ed ,target)))
   2349             ((default-connection)
   2350              (with-connection ((default-connection))
   2351                (send-oob-to-emacs `(:ed ,target))))
   2352             (t (error "No connection"))))))
   2353 
   2354 (defslyfun inspect-in-emacs (what &key wait)
   2355   "Inspect WHAT in Emacs. If WAIT is true (default NIL) blocks until the
   2356 inspector has been closed in Emacs."
   2357   (flet ((send-it ()
   2358            (let ((tag (when wait (make-tag)))
   2359                  (thread (when wait (current-thread-id))))
   2360              (with-buffer-syntax ()
   2361                (reset-inspector)
   2362                (send-oob-to-emacs `(:inspect ,(inspect-object what)
   2363                                              ,thread
   2364                                              ,tag)))
   2365              (when wait
   2366                (wait-for-event `(:emacs-return ,tag result))))))
   2367     (cond
   2368       (*emacs-connection*
   2369        (send-it))
   2370       ((default-connection)
   2371        (with-connection ((default-connection))
   2372          (send-it))))
   2373     what))
   2374 
   2375 (defslyfun value-for-editing (form)
   2376   "Return a readable value of FORM for editing in Emacs.
   2377 FORM is expected, but not required, to be SETF'able."
   2378   ;; FIXME: Can we check FORM for setfability? -luke (12/Mar/2005)
   2379   (with-buffer-syntax ()
   2380     (let* ((value (eval (read-from-string form)))
   2381            (*print-length* nil))
   2382       (prin1-to-string value))))
   2383 
   2384 (defslyfun commit-edited-value (form value)
   2385   "Set the value of a setf'able FORM to VALUE.
   2386 FORM and VALUE are both strings from Emacs."
   2387   (with-buffer-syntax ()
   2388     (eval `(setf ,(read-from-string form)
   2389             ,(read-from-string (concatenate 'string "`" value))))
   2390     t))
   2391 
   2392 (defun background-message  (format-string &rest args)
   2393   "Display a message in Emacs' echo area.
   2394 
   2395 Use this function for informative messages only.  The message may even
   2396 be dropped if we are too busy with other things."
   2397   (when *emacs-connection*
   2398     (send-to-emacs `(:background-message
   2399                      ,(apply #'format nil format-string args)))))
   2400 
   2401 ;; This is only used by the test suite.
   2402 (defun sleep-for (seconds)
   2403   "Sleep for at least SECONDS seconds.
   2404 This is just like cl:sleep but guarantees to sleep
   2405 at least SECONDS."
   2406   (let* ((start (get-internal-real-time))
   2407          (end (+ start
   2408                  (* seconds internal-time-units-per-second))))
   2409     (loop
   2410      (let ((now (get-internal-real-time)))
   2411        (cond ((< end now) (return))
   2412              (t (sleep (/ (- end now)
   2413                           internal-time-units-per-second))))))))
   2414 
   2415 
   2416 ;;;; Debugger
   2417 
   2418 (defun invoke-sly-debugger (condition)
   2419   "Sends a message to Emacs declaring that the debugger has been entered,
   2420 then waits to handle further requests from Emacs. Eventually returns
   2421 after Emacs causes a restart to be invoked."
   2422   (without-sly-interrupts
   2423     (cond (*emacs-connection*
   2424            (debug-in-emacs condition))
   2425           ((default-connection)
   2426            (with-connection ((default-connection))
   2427              (debug-in-emacs condition))))))
   2428 
   2429 (define-condition invoke-default-debugger () ())
   2430 
   2431 (defun slynk-debugger-hook (condition hook)
   2432   "Debugger function for binding *DEBUGGER-HOOK*."
   2433   (declare (ignore hook))
   2434   (handler-case
   2435       (call-with-debugger-hook #'slynk-debugger-hook
   2436                                (lambda () (invoke-sly-debugger condition)))
   2437     (invoke-default-debugger ()
   2438       (invoke-default-debugger condition))))
   2439 
   2440 (defun invoke-default-debugger (condition)
   2441   (call-with-debugger-hook nil (lambda () (invoke-debugger condition))))
   2442 
   2443 (defvar *global-debugger* t
   2444   "Non-nil means the Slynk debugger hook will be installed globally.")
   2445 
   2446 (add-hook *new-connection-hook* 'install-debugger)
   2447 (defun install-debugger (connection)
   2448   (declare (ignore connection))
   2449   (when *global-debugger*
   2450     (install-debugger-globally #'slynk-debugger-hook)))
   2451 
   2452 ;;;;; Debugger loop
   2453 ;;;
   2454 ;;; These variables are dynamically bound during debugging.
   2455 ;;;
   2456 (defvar *slynk-debugger-condition* nil
   2457   "The condition being debugged.")
   2458 
   2459 (defvar *sly-db-level* 0
   2460   "The current level of recursive debugging.")
   2461 
   2462 (defvar *sly-db-initial-frames* 20
   2463   "The initial number of backtrace frames to send to Emacs.")
   2464 
   2465 (defvar *sly-db-restarts* nil
   2466   "The list of currenlty active restarts.")
   2467 
   2468 (defvar *sly-db-stepping-p* nil
   2469   "True during execution of a step command.")
   2470 
   2471 (defun debug-in-emacs (condition)
   2472   (let ((*slynk-debugger-condition* condition)
   2473         (*sly-db-restarts* (compute-restarts condition))
   2474         (*sly-db-quit-restart* (and *sly-db-quit-restart*
   2475                                     (find-restart *sly-db-quit-restart*
   2476                                                   condition)))
   2477         (*package* (or (and (boundp '*buffer-package*)
   2478                             (symbol-value '*buffer-package*))
   2479                        *package*))
   2480         (*sly-db-level* (1+ *sly-db-level*))
   2481         (*sly-db-stepping-p* nil))
   2482     (force-user-output)
   2483     (call-with-debugging-environment
   2484      (lambda ()
   2485        (sly-db-loop *sly-db-level*)))))
   2486 
   2487 (defun sly-db-loop (level)
   2488   (unwind-protect
   2489        (loop
   2490         (with-simple-restart (abort "Return to sly-db level ~D." level)
   2491           (send-to-emacs
   2492            (list* :debug (current-thread-id) level
   2493                   (debugger-info-for-emacs 0 *sly-db-initial-frames*)))
   2494           (send-to-emacs
   2495            (list :debug-activate (current-thread-id) level))
   2496           (loop
   2497            (handler-case
   2498                (destructure-case (wait-for-event
   2499                                   `(or (:emacs-rex . _)
   2500                                        (:emacs-channel-send . _)
   2501                                        (:sly-db-return ,(1+ level))))
   2502                  ((:emacs-rex &rest args) (apply #'eval-for-emacs args))
   2503                  ((:emacs-channel-send channel (selector &rest args))
   2504                   (channel-send channel selector args))
   2505                  ((:sly-db-return _) (declare (ignore _)) (return nil)))
   2506              (sly-db-condition (c)
   2507                (handle-sly-db-condition c))))))
   2508     (send-to-emacs `(:debug-return
   2509                      ,(current-thread-id) ,level ,*sly-db-stepping-p*))
   2510     (wait-for-event `(:sly-db-return ,(1+ level)) t) ; clean event-queue
   2511     (when (> level 1)
   2512       (send-event (current-thread) `(:sly-db-return ,level)))))
   2513 
   2514 (defun handle-sly-db-condition (condition)
   2515   "Handle an internal debugger condition.
   2516 Rather than recursively debug the debugger (a dangerous idea!), these
   2517 conditions are simply reported."
   2518   (let ((real-condition (original-condition condition)))
   2519     (send-to-emacs `(:debug-condition ,(current-thread-id)
   2520                                       ,(princ-to-string real-condition)))))
   2521 
   2522 (defun %%condition-message (condition)
   2523   (let ((limit (ash 1 16)))
   2524     (with-string-stream (stream :length limit)
   2525       (handler-case
   2526           (let ((*print-readably* nil)
   2527                 (*print-pretty* t)
   2528                 (*print-right-margin* 65)
   2529                 (*print-circle* t)
   2530                 (*print-length* (or *print-length* limit))
   2531                 (*print-level* (or *print-level* limit))
   2532                 (*print-lines* (or *print-lines* limit)))
   2533             (print-condition condition stream))
   2534         (serious-condition (c)
   2535           (ignore-errors
   2536             (with-standard-io-syntax
   2537               (let ((*print-readably* nil))
   2538                 (format stream "~&Error (~a) printing the following condition: " (type-of c))
   2539                 (print-unreadable-object (condition stream :type t
   2540                                                     :identity t))))))))))
   2541 
   2542 (defun %condition-message (condition)
   2543   (string-trim #(#\newline #\space #\tab)
   2544                (%%condition-message condition)))
   2545 
   2546 (defvar *sly-db-condition-printer* #'%condition-message
   2547   "Function called to print a condition to an SLY-DB buffer.")
   2548 
   2549 (defun safe-condition-message (condition)
   2550   "Print condition to a string, handling any errors during printing."
   2551   (funcall *sly-db-condition-printer* condition))
   2552 
   2553 (defvar *debugger-extra-options* nil
   2554   ;; JT@15/08/24: FIXME: Actually, with a nice and proper method-combination for
   2555   ;; interfaces (as was once quite bravely attempted by Helmut, this variable
   2556   ;; could go away and contribs could simply add methods to CONDITION-EXTRAS)
   2557   ;; 
   2558   "A property list of extra options describing a condition.
   2559 This works much like the CONDITION-EXTRAS interface, but can be
   2560 dynamically bound by contribs when invoking the debugger.")
   2561 
   2562 (defun debugger-condition-for-emacs ()
   2563   (list (safe-condition-message *slynk-debugger-condition*)
   2564         (format nil "   [Condition of type ~S]"
   2565                 (type-of *slynk-debugger-condition*))
   2566         (append (condition-extras *slynk-debugger-condition*)
   2567                 *debugger-extra-options*)))
   2568 
   2569 (defun format-restarts-for-emacs ()
   2570   "Return a list of restarts for *slynk-debugger-condition* in a
   2571 format suitable for Emacs."
   2572   (let ((*print-right-margin* most-positive-fixnum))
   2573     (loop for restart in *sly-db-restarts* collect
   2574           (list (format nil "~:[~;*~]~a"
   2575                         (eq restart *sly-db-quit-restart*)
   2576                         (restart-name restart))
   2577                 (with-output-to-string (stream)
   2578                   (without-printing-errors (:object restart
   2579                                             :stream stream
   2580                                             :msg "<<error printing restart>>")
   2581                     (princ restart stream)))))))
   2582 
   2583 ;;;;; SLY-DB entry points
   2584 
   2585 (defslyfun sly-db-break-with-default-debugger (dont-unwind)
   2586   "Invoke the default debugger."
   2587   (cond (dont-unwind
   2588          (invoke-default-debugger *slynk-debugger-condition*))
   2589         (t
   2590          (signal 'invoke-default-debugger))))
   2591 
   2592 (defslyfun backtrace (start end)
   2593   "Return a list ((I FRAME PLIST) ...) of frames from START to END.
   2594 
   2595 I is an integer, and can be used to reference the corresponding frame
   2596 from Emacs; FRAME is a string representation of an implementation's
   2597 frame."
   2598   (loop for frame in (compute-backtrace start end)
   2599         for i from start collect
   2600         (list* i (frame-to-string frame)
   2601                (ecase (frame-restartable-p frame)
   2602                  ((nil) nil)
   2603                  ((t) `((:restartable t)))))))
   2604 
   2605 (defun frame-to-string (frame)
   2606   (with-string-stream (stream :length (* (or *print-lines* 1)
   2607                                          (or *print-right-margin* 100))
   2608                               :bindings *backtrace-printer-bindings*)
   2609     (handler-case (print-frame frame stream)
   2610       (serious-condition ()
   2611         (format stream "[error printing frame]")))))
   2612 
   2613 (defslyfun debugger-info-for-emacs (start end)
   2614   "Return debugger state, with stack frames from START to END.
   2615 The result is a list:
   2616   (condition ({restart}*) ({stack-frame}*) (cont*))
   2617 where
   2618   condition   ::= (description type [extra])
   2619   restart     ::= (name description)
   2620   stack-frame ::= (number description [plist])
   2621   extra       ::= (:references and other random things)
   2622   cont        ::= continuation
   2623   plist       ::= (:restartable {nil | t | :unknown})
   2624 
   2625 condition---a pair of strings: message, and type.  If show-source is
   2626 not nil it is a frame number for which the source should be displayed.
   2627 
   2628 restart---a pair of strings: restart name, and description.
   2629 
   2630 stack-frame---a number from zero (the top), and a printed
   2631 representation of the frame's call.
   2632 
   2633 continuation---the id of a pending Emacs continuation.
   2634 
   2635 Below is an example return value. In this case the condition was a
   2636 division by zero (multi-line description), and only one frame is being
   2637 fetched (start=0, end=1).
   2638 
   2639  ((\"Arithmetic error DIVISION-BY-ZERO signalled.
   2640 Operation was KERNEL::DIVISION, operands (1 0).\"
   2641    \"[Condition of type DIVISION-BY-ZERO]\")
   2642   ((\"ABORT\" \"Return to Sly toplevel.\")
   2643    (\"ABORT\" \"Return to Top-Level.\"))
   2644   ((0 \"(KERNEL::INTEGER-/-INTEGER 1 0)\" (:restartable nil)))
   2645   (4))"
   2646   (list (debugger-condition-for-emacs)
   2647         (format-restarts-for-emacs)
   2648         (backtrace start end)
   2649         *pending-continuations*))
   2650 
   2651 (defun nth-restart (index)
   2652   (nth index *sly-db-restarts*))
   2653 
   2654 (defslyfun invoke-nth-restart (index)
   2655   (let ((restart (nth-restart index)))
   2656     (when restart
   2657       (let* ((prompt nil)
   2658              (*query-io*
   2659                (make-two-way-stream
   2660                 (make-input-stream
   2661                  (lambda ()
   2662                    (format nil "~a~%"
   2663                            (read-from-minibuffer-in-emacs
   2664                             (format nil "~a" (or prompt
   2665                                                  "[restart prompt] :"))))))
   2666                 (make-output-stream
   2667                  #'(lambda (s)
   2668                      (setq prompt
   2669                            (concatenate 'string
   2670                                         (or prompt "")
   2671                                         s)))))))
   2672         (invoke-restart-interactively restart)))))
   2673 
   2674 (defslyfun sly-db-abort ()
   2675   (invoke-restart (find 'abort *sly-db-restarts* :key #'restart-name)))
   2676 
   2677 (defslyfun sly-db-continue ()
   2678   (continue))
   2679 
   2680 (defun coerce-to-condition (datum args)
   2681   (etypecase datum
   2682     (string (make-condition 'simple-error :format-control datum
   2683                             :format-arguments args))
   2684     (symbol (apply #'make-condition datum args))))
   2685 
   2686 (defslyfun simple-break (&optional (datum "Interrupt from Emacs") &rest args)
   2687   (with-simple-restart (continue "Continue from break.")
   2688     (invoke-sly-debugger (coerce-to-condition datum args))))
   2689 
   2690 ;; FIXME: (last (compute-restarts)) looks dubious.
   2691 (defslyfun throw-to-toplevel ()
   2692   "Invoke the ABORT-REQUEST restart abort an RPC from Emacs.
   2693 If we are not evaluating an RPC then ABORT instead."
   2694   (let ((restart (or (and *sly-db-quit-restart*
   2695                           (find-restart *sly-db-quit-restart*))
   2696                      (car (last (compute-restarts))))))
   2697     (cond (restart (invoke-restart restart))
   2698           (t (format nil "Restart not active [~s]" *sly-db-quit-restart*)))))
   2699 
   2700 (defslyfun invoke-nth-restart-for-emacs (sly-db-level n)
   2701   "Invoke the Nth available restart.
   2702 SLY-DB-LEVEL is the debug level when the request was made. If this
   2703 has changed, ignore the request."
   2704   (when (= sly-db-level *sly-db-level*)
   2705     (invoke-nth-restart n)))
   2706 
   2707 (defun wrap-sly-db-vars (form)
   2708   `(let ((*sly-db-level* ,*sly-db-level*))
   2709      ,form))
   2710 
   2711 (defun eval-in-frame-aux (frame string package print)
   2712   (let* ((form (wrap-sly-db-vars (parse-string string package)))
   2713          (values (multiple-value-list (eval-in-frame form frame))))
   2714     (with-buffer-syntax (package)
   2715       (funcall print values))))
   2716 
   2717 (defslyfun eval-string-in-frame (string frame package)
   2718   (eval-in-frame-aux frame string package #'echo-for-emacs))
   2719 
   2720 (defslyfun pprint-eval-string-in-frame (string frame package)
   2721   (eval-in-frame-aux frame string package #'slynk-pprint-values))
   2722 
   2723 (defslyfun frame-package-name (frame)
   2724   (let ((pkg (frame-package frame)))
   2725     (cond (pkg (package-name pkg))
   2726           (t (with-buffer-syntax () (package-name *package*))))))
   2727 
   2728 (defslyfun frame-locals-and-catch-tags (index)
   2729   "Return a list (LOCALS TAGS) for vars and catch tags in the frame INDEX.
   2730 LOCALS is a list of the form ((&key NAME ID VALUE) ...).
   2731 TAGS has is a list of strings."
   2732   (list (frame-locals-for-emacs index)
   2733         (mapcar #'to-string (frame-catch-tags index))))
   2734 
   2735 (defun frame-locals-for-emacs (index)
   2736   (loop for var in (frame-locals index)
   2737         collect
   2738         (destructuring-bind (&key name id value) var
   2739           (list :name (let ((*package* (or (frame-package index) *package*)))
   2740                         (prin1-to-string name))
   2741                 :id id
   2742                 :value
   2743                 (let ((*slynk-pprint-bindings*
   2744                         (append *slynk-pprint-bindings*
   2745                                 *backtrace-printer-bindings*)))
   2746                   (slynk-pprint value))))))
   2747 
   2748 (defslyfun sly-db-disassemble (index)
   2749   (with-output-to-string (*standard-output*)
   2750     (disassemble-frame index)))
   2751 
   2752 (defslyfun sly-db-return-from-frame (index string)
   2753   (let ((form (from-string string)))
   2754     (to-string (multiple-value-list (return-from-frame index form)))))
   2755 
   2756 (defslyfun sly-db-break (name)
   2757   (with-buffer-syntax ()
   2758     (sly-db-break-at-start (read-from-string name))))
   2759 
   2760 (defmacro define-stepper-function (name backend-function-name)
   2761   `(defslyfun ,name (frame)
   2762      (cond ((sly-db-stepper-condition-p *slynk-debugger-condition*)
   2763             (setq *sly-db-stepping-p* t)
   2764             (,backend-function-name))
   2765            ((find-restart 'continue)
   2766             (activate-stepping frame)
   2767             (setq *sly-db-stepping-p* t)
   2768             (continue))
   2769            (t
   2770             (error "Not currently single-stepping, ~
   2771 and no continue restart available.")))))
   2772 
   2773 (define-stepper-function sly-db-step sly-db-step-into)
   2774 (define-stepper-function sly-db-next sly-db-step-next)
   2775 (define-stepper-function sly-db-out  sly-db-step-out)
   2776 
   2777 (defslyfun toggle-break-on-signals ()
   2778   (setq *break-on-signals* (not *break-on-signals*))
   2779   (format nil "*break-on-signals* = ~a" *break-on-signals*))
   2780 
   2781 (defslyfun sdlb-print-condition ()
   2782   (princ-to-string *slynk-debugger-condition*))
   2783 
   2784 
   2785 ;;;; Compilation Commands.
   2786 
   2787 (defstruct (compilation-result (:type list))
   2788   (type :compilation-result)
   2789   notes
   2790   (successp nil :type boolean)
   2791   (duration 0.0 :type float)
   2792   (loadp nil :type boolean)
   2793   (faslfile nil :type (or null string)))
   2794 
   2795 (defun measure-time-interval (fun)
   2796   "Call FUN and return the first return value and the elapsed time.
   2797 The time is measured in seconds."
   2798   (declare (type function fun))
   2799   (let ((before (get-internal-real-time))) ;
   2800     (values
   2801      (funcall fun)
   2802      (/ (- (get-internal-real-time) before)
   2803         (coerce internal-time-units-per-second 'float)))))
   2804 
   2805 (defun make-compiler-note (condition)
   2806   "Make a compiler note data structure from a compiler-condition."
   2807   (declare (type compiler-condition condition))
   2808   (list* :message (message condition)
   2809          :severity (severity condition)
   2810          :location (location condition)
   2811          :references (references condition)
   2812          (let ((s (source-context condition)))
   2813            (if s (list :source-context s)))))
   2814 
   2815 (defun collect-notes (function)
   2816   (let ((notes '()))
   2817     (multiple-value-bind (result seconds)
   2818         (handler-bind ((compiler-condition
   2819                         (lambda (c) (push (make-compiler-note c) notes))))
   2820           (measure-time-interval
   2821            (lambda ()
   2822              ;; To report location of error-signaling toplevel forms
   2823              ;; for errors in EVAL-WHEN or during macroexpansion.
   2824              (restart-case (multiple-value-list (funcall function))
   2825                (abort () :report "Abort compilation." (list nil))))))
   2826       (destructuring-bind (successp &optional loadp faslfile) result
   2827         (let ((faslfile (etypecase faslfile
   2828                           (null nil)
   2829                           (pathname (pathname-to-filename faslfile)))))
   2830           (make-compilation-result :notes (reverse notes)
   2831                                    :duration seconds
   2832                                    :successp (if successp t)
   2833                                    :loadp (if loadp t)
   2834                                    :faslfile faslfile))))))
   2835 
   2836 (defun slynk-compile-file* (pathname load-p &rest options &key policy
   2837                                                       &allow-other-keys)
   2838   (multiple-value-bind (output-pathname warnings? failure?)
   2839       (slynk-compile-file pathname
   2840                           (fasl-pathname pathname options)
   2841                           nil
   2842                           (or (guess-external-format pathname)
   2843                               :default)
   2844                           :policy policy)
   2845     (declare (ignore warnings?))
   2846     (values t (not failure?) load-p output-pathname)))
   2847 
   2848 (defvar *compile-file-for-emacs-hook* '(slynk-compile-file*))
   2849 
   2850 (defslyfun compile-file-for-emacs (filename load-p &rest options)
   2851   "Compile FILENAME and, when LOAD-P, load the result.
   2852 Record compiler notes signalled as `compiler-condition's."
   2853   (with-buffer-syntax ()
   2854     (collect-notes
   2855      (lambda ()
   2856        (let ((pathname (filename-to-pathname filename))
   2857              (*compile-print* nil)
   2858              (*compile-verbose* t))
   2859          (loop for hook in *compile-file-for-emacs-hook*
   2860                do
   2861                (multiple-value-bind (tried success load? output-pathname)
   2862                    (apply hook pathname load-p options)
   2863                  (when tried
   2864                    (return (values success load? output-pathname))))))))))
   2865 
   2866 ;; FIXME: now that *compile-file-for-emacs-hook* is there this is
   2867 ;; redundant and confusing.
   2868 (defvar *fasl-pathname-function* nil
   2869   "In non-nil, use this function to compute the name for fasl-files.")
   2870 
   2871 (defun pathname-as-directory (pathname)
   2872   (append (pathname-directory pathname)
   2873           (when (pathname-name pathname)
   2874             (list (file-namestring pathname)))))
   2875 
   2876 (defun compile-file-output (file directory)
   2877   (make-pathname :directory (pathname-as-directory directory)
   2878                  :defaults (compile-file-pathname file)))
   2879 
   2880 (defun fasl-pathname (input-file options)
   2881   (cond (*fasl-pathname-function*
   2882          (funcall *fasl-pathname-function* input-file options))
   2883         ((getf options :fasl-directory)
   2884          (let ((dir (getf options :fasl-directory)))
   2885            (assert (char= (aref dir (1- (length dir))) #\/))
   2886            (compile-file-output input-file dir)))
   2887         (t
   2888          (compile-file-pathname input-file))))
   2889 
   2890 (defslyfun compile-string-for-emacs (string buffer position filename policy)
   2891   "Compile STRING (exerpted from BUFFER at POSITION).
   2892 Record compiler notes signalled as `compiler-condition's."
   2893   (let* ((offset (cadr (assoc :position position)))
   2894          (line-column (cdr (assoc :line position)))
   2895          (line (first line-column))
   2896          (column (second line-column)))
   2897     (with-buffer-syntax ()
   2898       (collect-notes
   2899        (lambda ()
   2900          (let ((*compile-print* nil)
   2901                (*compile-verbose* nil)
   2902                (*load-verbose* nil))
   2903            (slynk-compile-string string
   2904                                  :buffer buffer
   2905                                  :position offset
   2906                                  :filename filename
   2907                                  :line line
   2908                                  :column column
   2909                                  :policy policy)))))))
   2910 
   2911 (defslyfun compile-multiple-strings-for-emacs (strings policy)
   2912   "Compile STRINGS (exerpted from BUFFER at POSITION).
   2913 Record compiler notes signalled as `compiler-condition's."
   2914   (loop for (string buffer package position filename) in strings collect
   2915         (collect-notes
   2916          (lambda ()
   2917            (with-buffer-syntax (package)
   2918              (let ((*compile-print* t) (*compile-verbose* nil))
   2919                (slynk-compile-string string
   2920                                      :buffer buffer
   2921                                      :position position
   2922                                      :filename filename
   2923                                      :policy policy)))))))
   2924 
   2925 (defun file-newer-p (new-file old-file)
   2926   "Returns true if NEW-FILE is newer than OLD-FILE."
   2927   (> (file-write-date new-file) (file-write-date old-file)))
   2928 
   2929 (defun requires-compile-p (source-file)
   2930   (let ((fasl-file (probe-file (compile-file-pathname source-file))))
   2931     (or (not fasl-file)
   2932         (file-newer-p source-file fasl-file))))
   2933 
   2934 (defslyfun compile-file-if-needed (filename loadp)
   2935   (let ((pathname (filename-to-pathname filename)))
   2936     (cond ((requires-compile-p pathname)
   2937            (compile-file-for-emacs pathname loadp))
   2938           (t
   2939            (collect-notes
   2940             (lambda ()
   2941               (or (not loadp)
   2942                   (load (compile-file-pathname pathname)))))))))
   2943 
   2944 
   2945 ;;;; Loading
   2946 
   2947 (defslyfun load-file (filename)
   2948   (to-string (load (filename-to-pathname filename))))
   2949 
   2950 
   2951 ;;;;; slynk-require
   2952 
   2953 (defvar *module-loading-method* (find-if #'find-package '(:slynk-loader :asdf))
   2954   "Keyword naming the module-loading method.
   2955 
   2956 SLY's own `slynk-loader.lisp' is tried first, then ASDF")
   2957 
   2958 (defvar *asdf-load-in-progress* nil
   2959   "Set to t if inside a \"ASDF:LOAD-SYSTEM\" operation.
   2960 Introduced to prevent problematic recursive ASDF loads, but going away
   2961 soon once non-ASDF loading is removed. (see github#134)")
   2962 
   2963 (defgeneric require-module (method module)
   2964   (:documentation
   2965    "Use METHOD to load MODULE.
   2966 Receives a module name as argument and should return non-nil if it
   2967 managed to load it.")
   2968   (:method ((method (eql :slynk-loader)) module)
   2969     (funcall (intern "REQUIRE-MODULE" :slynk-loader) module))
   2970   (:method ((method (eql :asdf)) module)
   2971     (unless *asdf-load-in-progress*
   2972       (let ((*asdf-load-in-progress* t))
   2973         (funcall (intern "LOAD-SYSTEM" :asdf) module)))))
   2974 
   2975 (defun add-to-load-path-1 (path load-path-var)
   2976   (pushnew path (symbol-value load-path-var) :test #'equal))
   2977 
   2978 (defgeneric add-to-load-path (method path)
   2979   (:documentation
   2980    "Using METHOD, consider PATH when searching for modules.")
   2981   (:method ((method (eql :slynk-loader)) path)
   2982     (add-to-load-path-1 path (intern "*LOAD-PATH*" :slynk-loader)))
   2983   (:method ((method (eql :asdf)) path)
   2984     (add-to-load-path-1 path (intern "*CENTRAL-REGISTRY*" :asdf))))
   2985 
   2986 (defvar *slynk-require-hook* '()
   2987   "Functions run after SLYNK-REQUIRE. Called with new modules.")
   2988 
   2989 (defslyfun slynk-require (modules)
   2990   "Load each module in MODULES.
   2991 
   2992 MODULES is a list of strings designators or a single string
   2993 designator. Returns a list of all modules available."
   2994   (let ((loaded))
   2995     (dolist (module (ensure-list modules))
   2996       (with-simple-restart (continue "Continue without SLY contrib ~a" module)
   2997         (funcall #'require-module *module-loading-method* module)
   2998         (push module loaded)
   2999         (pushnew (string-upcase module) *modules* :test #'equal))
   3000       (loop for fn in *slynk-require-hook*
   3001             do (funcall fn loaded)))
   3002     (list *modules* loaded)))
   3003 
   3004 (defslyfun slynk-add-load-paths (paths)
   3005   (dolist (path paths)
   3006     (funcall #'add-to-load-path *module-loading-method* (pathname path))))
   3007 
   3008 
   3009 ;;;; Macroexpansion
   3010 
   3011 (defvar *macroexpand-printer-bindings*
   3012   '((*print-circle* . nil)
   3013     (*print-pretty* . t)
   3014     (*print-escape* . t)
   3015     (*print-lines* . nil)
   3016     (*print-level* . nil)
   3017     (*print-length* . nil)
   3018     (*print-case* . :downcase))
   3019   "Pretty-pretty bindings to use when expanding macros")
   3020 
   3021 (defun apply-macro-expander (expander string)
   3022   (with-buffer-syntax ()
   3023     (let ((expansion (funcall expander (from-string string))))
   3024       (with-bindings *macroexpand-printer-bindings*
   3025         (prin1-to-string expansion)))))
   3026 
   3027 (defslyfun slynk-macroexpand-1 (string)
   3028   (apply-macro-expander #'macroexpand-1 string))
   3029 
   3030 (defslyfun slynk-macroexpand (string)
   3031   (apply-macro-expander #'macroexpand string))
   3032 
   3033 (defslyfun slynk-macroexpand-all (string)
   3034   (apply-macro-expander #'macroexpand-all string))
   3035 
   3036 (defslyfun slynk-compiler-macroexpand-1 (string)
   3037   (apply-macro-expander #'compiler-macroexpand-1 string))
   3038 
   3039 (defslyfun slynk-compiler-macroexpand (string)
   3040   (apply-macro-expander #'compiler-macroexpand string))
   3041 
   3042 (defslyfun slynk-expand-1 (string)
   3043   (apply-macro-expander #'expand-1 string))
   3044 
   3045 (defslyfun slynk-expand (string)
   3046   (apply-macro-expander #'expand string))
   3047 
   3048 (defun expand-1 (form)
   3049   (multiple-value-bind (expansion expanded?) (macroexpand-1 form)
   3050     (if expanded?
   3051         (values expansion t)
   3052         (compiler-macroexpand-1 form))))
   3053 
   3054 (defun expand (form)
   3055   (expand-repeatedly #'expand-1 form))
   3056 
   3057 (defun expand-repeatedly (expander form)
   3058   (loop
   3059     (multiple-value-bind (expansion expanded?) (funcall expander form)
   3060       (unless expanded? (return expansion))
   3061       (setq form expansion))))
   3062 
   3063 (defslyfun slynk-format-string-expand (string)
   3064   (apply-macro-expander #'format-string-expand string))
   3065 
   3066 (defslyfun disassemble-form (form)
   3067   (with-buffer-syntax ()
   3068     (with-output-to-string (*standard-output*)
   3069       (let ((*print-readably* nil))
   3070         (disassemble (eval (read-from-string form)))))))
   3071 
   3072 
   3073 ;;;; Simple arglist display
   3074 
   3075 (defslyfun operator-arglist (name package)
   3076   (ignore-errors
   3077    (let ((args (arglist (parse-symbol name (guess-buffer-package package)))))
   3078      (cond ((eq args :not-available) nil)
   3079            (t (princ-to-string (cons name args)))))))
   3080 
   3081 
   3082 ;;;; Documentation
   3083 
   3084 (defun map-if (test fn &rest lists)
   3085   "Like (mapcar FN . LISTS) but only call FN on objects satisfying TEST.
   3086 Example:
   3087 \(map-if #'oddp #'- '(1 2 3 4 5)) => (-1 2 -3 4 -5)"
   3088   (apply #'mapcar
   3089          (lambda (x) (if (funcall test x) (funcall fn x) x))
   3090          lists))
   3091 
   3092 (defun listify (f)
   3093   "Return a function like F, but which returns any non-null value
   3094 wrapped in a list."
   3095   (lambda (x)
   3096     (let ((y (funcall f x)))
   3097       (and y (list y)))))
   3098 
   3099 (defun call-with-describe-settings (fn)
   3100   (let ((*print-readably* nil))
   3101     (funcall fn)))
   3102 
   3103 (defmacro with-describe-settings ((&rest _) &body body)
   3104   (declare (ignore _))
   3105   `(call-with-describe-settings (lambda () ,@body)))
   3106 
   3107 (defun describe-to-string (object)
   3108   (with-describe-settings ()
   3109     (with-output-to-string (*standard-output*)
   3110       (describe object))))
   3111 
   3112 (defslyfun describe-symbol (symbol-name)
   3113   (with-buffer-syntax ()
   3114     (describe-to-string (parse-symbol-or-lose symbol-name))))
   3115 
   3116 (defslyfun describe-function (name)
   3117   (with-buffer-syntax ()
   3118     (let ((symbol (parse-symbol-or-lose name)))
   3119       (describe-to-string (or (macro-function symbol)
   3120                               (symbol-function symbol))))))
   3121 
   3122 (defslyfun describe-definition-for-emacs (name kind)
   3123   (with-buffer-syntax ()
   3124     (with-describe-settings ()
   3125       (with-output-to-string (*standard-output*)
   3126         (describe-definition (parse-symbol-or-lose name) kind)))))
   3127 
   3128 (defslyfun documentation-symbol (symbol-name)
   3129   (with-buffer-syntax ()
   3130     (multiple-value-bind (sym foundp) (parse-symbol symbol-name)
   3131       (if foundp
   3132           (let ((vdoc (documentation sym 'variable))
   3133                 (fdoc (documentation sym 'function)))
   3134             (with-output-to-string (string)
   3135               (format string "Documentation for the symbol ~a:~2%" sym)
   3136               (unless (or vdoc fdoc)
   3137                 (format string "Not documented." ))
   3138               (when vdoc
   3139                 (format string "Variable:~% ~a~2%" vdoc))
   3140               (when fdoc
   3141                 (format string "Function:~% Arglist: ~a~2% ~a"
   3142                         (slynk-backend:arglist sym)
   3143                         fdoc))))
   3144           (format nil "No such symbol, ~a." symbol-name)))))
   3145 
   3146 
   3147 ;;;; Package Commands
   3148 
   3149 (defslyfun list-all-package-names (&optional nicknames)
   3150   "Return a list of all package names.
   3151 Include the nicknames if NICKNAMES is true."
   3152   (mapcar #'unparse-name
   3153           (if nicknames
   3154               (mapcan #'package-names (list-all-packages))
   3155               (mapcar #'package-name  (list-all-packages)))))
   3156 
   3157 
   3158 ;;;; Tracing
   3159 
   3160 ;; Use eval for the sake of portability...
   3161 (defun tracedp (fspec)
   3162   (member fspec (eval '(trace))))
   3163 
   3164 (defvar *after-toggle-trace-hook* nil
   3165   "Hook called whenever a SPEC is traced or untraced.
   3166 
   3167 If non-nil, called with two arguments SPEC and TRACED-P." )
   3168 (defslyfun slynk-toggle-trace (spec-string)
   3169   (let* ((spec (from-string spec-string))
   3170          (retval (cond ((consp spec) ; handle complicated cases in the backend
   3171                         (toggle-trace spec))
   3172                        ((tracedp spec)
   3173                         (eval `(untrace ,spec))
   3174                         (format nil "~S is now untraced." spec))
   3175                        (t
   3176                         (eval `(trace ,spec))
   3177                         (format nil "~S is now traced." spec))))
   3178          (traced-p (let* ((tosearch "is now traced.")
   3179                           (start (- (length retval)
   3180                                     (length tosearch)))
   3181                           (end (+ start (length tosearch))))
   3182                      (search tosearch (subseq retval start end))))
   3183          (hook-msg (when *after-toggle-trace-hook*
   3184                      (funcall *after-toggle-trace-hook*
   3185                               spec
   3186                               traced-p))))
   3187     (if hook-msg
   3188         (format nil "~a~%(also ~a)" retval hook-msg)
   3189         retval)))
   3190 
   3191 (defslyfun untrace-all ()
   3192   (untrace))
   3193 
   3194 
   3195 ;;;; Undefing
   3196 
   3197 (defslyfun undefine-function (fname-string)
   3198   (let ((fname (from-string fname-string)))
   3199     (format nil "~S" (fmakunbound fname))))
   3200 
   3201 (defun read-as-function (name)
   3202   (eval (from-string (format nil "(function ~A)" name))))
   3203 
   3204 (defslyfun remove-method-by-name (generic-name qualifiers specializers)
   3205   "Remove GENERIC-NAME's method with QUALIFIERS and SPECIALIZERS."
   3206   (let* ((generic-function (read-as-function generic-name))
   3207          (qualifiers (mapcar #'from-string qualifiers))
   3208          (specializers (mapcar #'from-string specializers))
   3209          (method (find-method generic-function qualifiers specializers)))
   3210     (remove-method generic-function method)
   3211     t))
   3212 
   3213 (defslyfun generic-method-specs (generic-name)
   3214   "Compute ((QUALIFIERS SPECIALIZERS)...) for methods of GENERIC-NAME's gf.
   3215 QUALIFIERS and SPECIALIZERS are lists of strings."
   3216   (mapcar
   3217    (lambda (method)
   3218      (list (mapcar #'prin1-to-string (slynk-mop:method-qualifiers method))
   3219            (mapcar (lambda (specializer)
   3220                      (if (typep specializer 'slynk-mop:eql-specializer)
   3221                          (format nil "(eql ~A)"
   3222                                  (slynk-mop:eql-specializer-object specializer))
   3223                          (prin1-to-string (class-name specializer))))
   3224                    (slynk-mop:method-specializers method))))
   3225    (slynk-mop:generic-function-methods (read-as-function generic-name))))
   3226 
   3227 (defslyfun unintern-symbol (name package)
   3228   (let ((pkg (guess-package package)))
   3229     (cond ((not pkg) (format nil "No such package: ~s" package))
   3230           (t
   3231            (multiple-value-bind (sym found) (parse-symbol name pkg)
   3232              (case found
   3233                ((nil) (format nil "~s not in package ~s" name package))
   3234                (t
   3235                 (unintern sym pkg)
   3236                 (format nil "Uninterned symbol: ~s" sym))))))))
   3237 
   3238 (defslyfun slynk-delete-package (package-name)
   3239   (let ((pkg (or (guess-package package-name)
   3240                  (error "No such package: ~s" package-name))))
   3241     (delete-package pkg)
   3242     nil))
   3243 
   3244 ;;;; Source Locations
   3245 
   3246 (defslyfun find-definition-for-thing (thing)
   3247   (find-source-location thing))
   3248 
   3249 (defslyfun find-source-location-for-emacs (spec)
   3250   (find-source-location (value-spec-ref spec)))
   3251 
   3252 (defun value-spec-ref (spec)
   3253   (destructure-case spec
   3254     ((:string string package)
   3255      (with-buffer-syntax (package)
   3256        (eval (read-from-string string))))
   3257     ((:inspector part)
   3258      (inspector-nth-part part))
   3259     ((:sly-db frame var)
   3260      (frame-var-value frame var))))
   3261 
   3262 (defvar *find-definitions-right-trim* ",:.>")
   3263 (defvar *find-definitions-left-trim* "#:<")
   3264 
   3265 (defun find-definitions-find-symbol-or-package (name)
   3266   (flet ((do-find (name)
   3267            (multiple-value-bind (symbol found name)
   3268                (with-buffer-syntax ()
   3269                  (parse-symbol name))
   3270              (cond (found
   3271                     (return-from find-definitions-find-symbol-or-package
   3272                       (values symbol found)))
   3273                    ;; Packages are not named by symbols, so
   3274                    ;; not-interned symbols can refer to packages
   3275                    ((find-package name)
   3276                     (return-from find-definitions-find-symbol-or-package
   3277                       (values (make-symbol name) t)))))))
   3278     (do-find name)
   3279     (do-find (string-right-trim *find-definitions-right-trim* name))
   3280     (do-find (string-left-trim *find-definitions-left-trim* name))
   3281     (do-find (string-left-trim *find-definitions-left-trim*
   3282                                (string-right-trim
   3283                                 *find-definitions-right-trim* name)))
   3284     ;; Not exactly robust
   3285     (when (and (eql (search "(setf " name :test #'char-equal) 0)
   3286                (char= (char name (1- (length name))) #\)))
   3287       (multiple-value-bind (symbol found)
   3288           (with-buffer-syntax ()
   3289             (parse-symbol (subseq name (length "(setf ")
   3290                                   (1- (length name)))))
   3291         (when found
   3292           (values `(setf ,symbol) t))))))
   3293 
   3294 (defslyfun find-definitions-for-emacs (name)
   3295   "Return a list ((DSPEC LOCATION) ...) of definitions for NAME.
   3296 DSPEC is a string and LOCATION a source location. NAME is a string."
   3297   (multiple-value-bind (symbol found)
   3298       (find-definitions-find-symbol-or-package name)
   3299     (when found
   3300       (mapcar #'xref>elisp (find-definitions symbol)))))
   3301 
   3302 ;;; Generic function so contribs can extend it.
   3303 (defgeneric xref-doit (type thing)
   3304   (:method (type thing)
   3305     (declare (ignore type thing))
   3306     :not-implemented))
   3307 
   3308 (macrolet ((define-xref-action (xref-type handler)
   3309              `(defmethod xref-doit ((type (eql ,xref-type)) thing)
   3310                 (declare (ignorable type))
   3311                 (funcall ,handler thing))))
   3312   (define-xref-action :calls        #'who-calls)
   3313   (define-xref-action :calls-who    #'calls-who)
   3314   (define-xref-action :references   #'who-references)
   3315   (define-xref-action :binds        #'who-binds)
   3316   (define-xref-action :sets         #'who-sets)
   3317   (define-xref-action :macroexpands #'who-macroexpands)
   3318   (define-xref-action :specializes  #'who-specializes)
   3319   (define-xref-action :callers      #'list-callers)
   3320   (define-xref-action :callees      #'list-callees))
   3321 
   3322 (defslyfun xref (type name)
   3323   (multiple-value-bind (sexp error) (ignore-errors (from-string name))
   3324     (unless error
   3325       (let ((xrefs  (xref-doit type sexp)))
   3326         (if (eq xrefs :not-implemented)
   3327             :not-implemented
   3328             (mapcar #'xref>elisp xrefs))))))
   3329 
   3330 (defslyfun xrefs (types name)
   3331   (loop for type in types
   3332         for xrefs = (xref type name)
   3333         when (and (not (eq :not-implemented xrefs))
   3334                   (not (null xrefs)))
   3335           collect (cons type xrefs)))
   3336 
   3337 (defun xref>elisp (xref)
   3338   (destructuring-bind (name loc) xref
   3339     (list (to-string name) loc)))
   3340 
   3341 
   3342 ;;;;; Lazy lists
   3343 
   3344 (defstruct (lcons (:constructor %lcons (car %cdr))
   3345                   (:predicate lcons?))
   3346   car
   3347   (%cdr nil :type (or null lcons function))
   3348   (forced? nil))
   3349 
   3350 (defmacro lcons (car cdr)
   3351   `(%lcons ,car (lambda () ,cdr)))
   3352 
   3353 (defmacro lcons* (car cdr &rest more)
   3354   (cond ((null more) `(lcons ,car ,cdr))
   3355         (t `(lcons ,car (lcons* ,cdr ,@more)))))
   3356 
   3357 (defun lcons-cdr (lcons)
   3358   (let ((cdr (lcons-%cdr lcons)))
   3359     (cond ((lcons-forced? lcons) cdr)
   3360           (t
   3361            (let ((value (funcall cdr)))
   3362              (setf (lcons-forced? lcons) t
   3363                    (lcons-%cdr lcons) value))))))
   3364 
   3365 (defun llist-range (llist start end)
   3366   (llist-take (llist-skip llist start) (- end start)))
   3367 
   3368 (defun llist-skip (lcons index)
   3369   (do ((i 0 (1+ i))
   3370        (l lcons (lcons-cdr l)))
   3371       ((or (= i index) (null l))
   3372        l)))
   3373 
   3374 (defun llist-take (lcons count)
   3375   (let ((result '()))
   3376     (do ((i 0 (1+ i))
   3377          (l lcons (lcons-cdr l)))
   3378         ((or (= i count)
   3379              (null l)))
   3380       (push (lcons-car l) result))
   3381     (nreverse result)))
   3382 
   3383 (defun iline (label value)
   3384   `(:line ,label ,value))
   3385 
   3386 
   3387 ;;;; Inspecting
   3388 (defvar-unbound *current-inspector*
   3389     "Current inspector, bound by EVAL-FOR-INSPECTOR, maybe to nil.")
   3390 
   3391 (defvar-unbound *target-inspector*
   3392     "Target inspector, bound by EVAL-FOR-INSPECTOR, maybe to nil.")
   3393 
   3394 (defun current-inspector ()
   3395   (or (and (boundp '*current-inspector*)
   3396            *current-inspector*)
   3397       (find-inspector "default")
   3398       (make-instance 'inspector :name "default")))
   3399 
   3400 (defun target-inspector ()
   3401   (or (and (boundp '*target-inspector*)
   3402            *target-inspector*)
   3403       (current-inspector)))
   3404 
   3405 
   3406 (defvar *inspector-printer-bindings*
   3407   '((*print-lines*        . 1)
   3408     (*print-right-margin* . 75)
   3409     (*print-pretty*       . t)
   3410     (*print-readably*     . nil)))
   3411 
   3412 (defvar *inspector-verbose-printer-bindings*
   3413   '((*print-escape* . t)
   3414     (*print-circle* . t)
   3415     (*print-array*  . nil)))
   3416 
   3417 (defclass inspector ()
   3418   ((verbose-p :initform nil :accessor inspector-verbose-p)
   3419    (history :initform (make-array 10 :adjustable t :fill-pointer 0) :accessor inspector-%history)
   3420    (name :initarg :name :initform (error "Name this INSPECTOR!") :accessor inspector-name)))
   3421 
   3422 (defmethod print-object ((i inspector) s)
   3423   (print-unreadable-object (i s :type t) 
   3424     (format s "~a/~a" (inspector-name i) (length (inspector-%history i)))))
   3425 
   3426 (defmethod initialize-instance :after ((i inspector) &key name)
   3427   (assert (not (find-inspector name)) nil "Already have an inspector named ~a" name)
   3428   (push i (connection-inspectors *emacs-connection*)))
   3429 
   3430 (defun find-inspector (name)
   3431   (find name (connection-inspectors *emacs-connection*)
   3432         :key #'inspector-name :test #'string=))
   3433 
   3434 (defstruct inspector-state)
   3435 (defstruct (istate (:conc-name istate.) (:include inspector-state))
   3436   object
   3437   (parts (make-array 10 :adjustable t :fill-pointer 0))
   3438   (actions (make-array 10 :adjustable t :fill-pointer 0))
   3439   metadata
   3440   content
   3441   serial)
   3442 
   3443 (defun ensure-istate-metadata (o indicator default)
   3444   (with-struct (istate. object metadata) (current-istate)
   3445     (assert (eq object o))
   3446     (let ((data (getf metadata indicator default)))
   3447       (setf (getf metadata indicator) data)
   3448       data)))
   3449 
   3450 (defun current-istate (&optional (inspector (current-inspector)))
   3451   (let* ((history (inspector-%history inspector)))
   3452     (and (plusp (length history))
   3453          (aref history (1- (length history))))))
   3454 
   3455 (defun reset-inspector (&optional (inspector (current-inspector)))
   3456   #+sbcl
   3457   ;; FIXME: On SBCL, for some silly reason, this is needed to lose the
   3458   ;; references to the history's objects (github##568)
   3459   (loop with hist = (inspector-%history inspector)
   3460         for i from 0 below (array-dimension hist 0)
   3461         do (setf (aref hist i) nil))
   3462   (setf (inspector-%history inspector)
   3463         (make-array 10 :adjustable t :fill-pointer 0)))
   3464 
   3465 (defslyfun init-inspector (string)
   3466   (with-buffer-syntax ()
   3467     (with-retry-restart (:msg "Retry SLY inspection request.")
   3468       (inspect-object (eval (read-from-string string))))))
   3469 
   3470 (defun inspect-object (o)
   3471   (let* ((inspector (target-inspector))
   3472          (history (inspector-%history inspector))
   3473          (istate (make-istate :object o)))
   3474     (vector-push-extend istate history)
   3475     (let ((*current-inspector* inspector))
   3476       ;; HACK! because EMACS-INSPECT may call ENSURE-ISTATE-METADATA
   3477       ;; which expects its object to be the current istate's objects.
   3478       (setf (istate.content istate)
   3479             (emacs-inspect o)))
   3480     (vector-push-extend :break-history history)
   3481     (decf (fill-pointer history))
   3482     (istate>elisp istate)))
   3483 
   3484 (defun istate>elisp (istate)
   3485   (list :title (prepare-title istate)
   3486         :id (assign-index (istate.object istate) (istate.parts istate))
   3487         :content (prepare-range istate 0 500)
   3488         ;; :serial (istate.serial istate)
   3489         ))
   3490 
   3491 (defun prepare-title (istate)
   3492   (if (inspector-verbose-p (current-inspector))
   3493       (with-bindings *inspector-verbose-printer-bindings*
   3494         (to-string (istate.object istate)))
   3495       (with-string-stream (stream :length 200
   3496                                   :bindings *inspector-printer-bindings*)
   3497         (print-unreadable-object
   3498             ((istate.object istate) stream :type t :identity t)))))
   3499 
   3500 (defun prepare-range (istate start end)
   3501   (let* ((range (content-range (istate.content istate) start end))
   3502          (ps (loop for part in range append (prepare-part part istate))))
   3503     (list ps
   3504           (if (< (length ps) (- end start))
   3505               (+ start (length ps))
   3506               (+ end 1000))
   3507           start end)))
   3508 
   3509 (defun prepare-part (part istate)
   3510   (let ((newline '#.(string #\newline)))
   3511     (etypecase part
   3512       (string (list part))
   3513       (cons (destructure-case part
   3514               ((:newline) (list newline))
   3515               ((:value obj &optional str)
   3516                (list (value-part obj str (istate.parts istate))))
   3517               ((:label &rest strs)
   3518                (list (list :label (apply #'cat (mapcar #'string strs)))))
   3519               ((:action label lambda &key (refreshp t))
   3520                (list (action-part label lambda refreshp
   3521                                   (istate.actions istate))))
   3522               ((:line label value)
   3523                (list (princ-to-string label) ": "
   3524                      (value-part value nil (istate.parts istate))
   3525                      newline)))))))
   3526 
   3527 (defun value-part (object string parts)
   3528   (list :value
   3529         (or string (print-part-to-string object))
   3530         (assign-index object parts)))
   3531 
   3532 (defun action-part (label lambda refreshp actions)
   3533   (list :action label (assign-index (list lambda refreshp) actions)))
   3534 
   3535 (defun assign-index (object vector)
   3536   (let ((index (fill-pointer vector)))
   3537     (vector-push-extend object vector)
   3538     index))
   3539 
   3540 (defun print-part-to-string (value)
   3541   (let* ((*print-readably* nil)
   3542          (string (slynk-pprint-to-line value))
   3543          (pos (position value
   3544                         (inspector-%history (current-inspector))
   3545                         :key #'istate.object)))
   3546     (if pos
   3547         (format nil "@~D=~A" pos string)
   3548         string)))
   3549 
   3550 (defun content-range (list start end)
   3551   (typecase list
   3552     (list (let ((len (length list)))
   3553             (subseq list start (min len end))))
   3554     (lcons (llist-range list start end))))
   3555 
   3556 (defslyfun inspector-nth-part (index)
   3557   "Return the current inspector's INDEXth part.
   3558 The second value indicates if that part exists at all."
   3559   (let* ((parts (istate.parts (current-istate)))
   3560          (foundp (< index (length parts))))
   3561     (values (and foundp (aref parts index))
   3562             foundp)))
   3563 
   3564 (defslyfun inspector-nth-part-or-lose (index)
   3565   "Return the current inspector's INDEXth part.
   3566 The second value indicates if that part exists at all."
   3567   (multiple-value-bind (part foundp)
   3568       (inspector-nth-part index)
   3569     (if foundp part (error "No part with index ~a" index))))
   3570 
   3571 (defslyfun inspect-nth-part (index)
   3572   (with-buffer-syntax ()
   3573     (inspect-object (inspector-nth-part index))))
   3574 
   3575 (defslyfun inspector-range (from to)
   3576   (prepare-range (current-istate) from to))
   3577 
   3578 (defslyfun inspector-call-nth-action (index &rest args)
   3579   (destructuring-bind (fun refreshp) (aref (istate.actions (current-istate)) index)
   3580     (apply fun args)
   3581     (if refreshp
   3582         (inspector-reinspect)
   3583         ;; tell emacs that we don't want to refresh the inspector buffer
   3584         nil)))
   3585 
   3586 (defslyfun inspector-pop ()
   3587   "Inspect the previous object.
   3588 Return nil if there's no previous object."
   3589   (with-buffer-syntax ()
   3590     (let* ((history (inspector-%history (current-inspector))))
   3591       (when (> (length history) 1)
   3592         (decf (fill-pointer history))
   3593         (istate>elisp (current-istate))))))
   3594 
   3595 (defslyfun inspector-next ()
   3596   "Inspect the next element in the history of inspected objects.."
   3597   (with-buffer-syntax ()
   3598     (let* ((history (inspector-%history (current-inspector))))
   3599       (when (and (< (fill-pointer history)
   3600                     (array-dimension history 0))
   3601                  (istate-p (aref history (fill-pointer history))))
   3602         (incf (fill-pointer history))
   3603         (istate>elisp (current-istate))))))
   3604 
   3605 (defslyfun inspector-reinspect ()
   3606   (let ((istate (current-istate)))
   3607     (setf (istate.content istate)
   3608           (emacs-inspect (istate.object istate)))
   3609     (istate>elisp istate)))
   3610 
   3611 (defslyfun inspector-toggle-verbose ()
   3612   "Toggle verbosity of inspected object."
   3613   (setf (inspector-verbose-p (current-inspector))
   3614         (not (inspector-verbose-p (current-inspector))))
   3615   (istate>elisp (current-istate)))
   3616 
   3617 (defslyfun inspector-eval (string)
   3618   (let* ((obj (istate.object (current-istate)))
   3619          (context (eval-context obj))
   3620          (form (with-buffer-syntax ((cdr (assoc '*package* context)))
   3621                  (read-from-string string)))
   3622          (ignorable (remove-if #'boundp (mapcar #'car context))))
   3623     (to-string (eval `(let ((* ',obj) (- ',form)
   3624                             . ,(loop for (var . val) in context
   3625                                      unless (constantp var) collect
   3626                                      `(,var ',val)))
   3627                         (declare (ignorable . ,ignorable))
   3628                         ,form)))))
   3629 
   3630 (defslyfun inspector-history ()
   3631   (slynk-pprint-to-line (inspector-%history (current-inspector))))
   3632 
   3633 (defslyfun quit-inspector ()
   3634   (reset-inspector)
   3635   nil)
   3636 
   3637 (defslyfun describe-inspectee ()
   3638   "Describe the currently inspected object."
   3639   (with-buffer-syntax ()
   3640     (describe-to-string (istate.object (current-istate)))))
   3641 
   3642 (defslyfun describe-inspector-part (index)
   3643   "Describe part INDEX of the currently inspected object."
   3644   (with-buffer-syntax ()
   3645     (describe-to-string (inspector-nth-part index))))
   3646 
   3647 (defslyfun pprint-inspector-part (index)
   3648   "Pretty-print part INDEX of the currently inspected object."
   3649   (with-buffer-syntax ()
   3650     (slynk-pprint (inspector-nth-part index))))
   3651 
   3652 (defslyfun inspect-in-frame (string index)
   3653   (with-buffer-syntax ()
   3654     (with-retry-restart (:msg "Retry SLY inspection request.")
   3655       (reset-inspector)
   3656       (inspect-object (eval-in-frame (from-string string) index)))))
   3657 
   3658 (defslyfun inspect-current-condition ()
   3659   (with-buffer-syntax ()
   3660     (reset-inspector)
   3661     (inspect-object *slynk-debugger-condition*)))
   3662 
   3663 (defslyfun inspect-frame-var (frame var)
   3664   (with-buffer-syntax ()
   3665     (reset-inspector)
   3666     (inspect-object (frame-var-value frame var))))
   3667 
   3668 (defslyfun pprint-frame-var (frame var)
   3669   (with-buffer-syntax ()
   3670     (slynk-pprint (frame-var-value frame var))))
   3671 
   3672 (defslyfun describe-frame-var (frame var)
   3673   (with-buffer-syntax ()
   3674     (describe-to-string (frame-var-value frame var))))
   3675 
   3676 (defslyfun eval-for-inspector (current
   3677                                target
   3678                                slave-slyfun &rest args)
   3679   "Call SLAVE-SLYFUN with ARGS in CURRENT inspector, open in TARGET."
   3680   (let ((*current-inspector* (and current
   3681                                   (or (find-inspector current)
   3682                                       (make-instance 'inspector :name current))))
   3683         (*target-inspector* (and target
   3684                                  (or (find-inspector target)
   3685                                      (make-instance 'inspector :name target)))))
   3686     (apply slave-slyfun args)))
   3687 
   3688 ;;;;; Lists
   3689 
   3690 (defmethod emacs-inspect ((o cons))
   3691   (if (listp (cdr o))
   3692       (inspect-list o)
   3693       (inspect-cons o)))
   3694 
   3695 (defun inspect-cons (cons)
   3696   (label-value-line*
   3697    ('car (car cons))
   3698    ('cdr (cdr cons))))
   3699 
   3700 (defun inspect-list (list)
   3701   (multiple-value-bind (length tail) (safe-length list)
   3702     (flet ((frob (title list)
   3703              (list* title '(:newline) (inspect-list-aux list))))
   3704       (cond ((not length)
   3705              (frob "A circular list:"
   3706                    (cons (car list)
   3707                          (ldiff (cdr list) list))))
   3708             ((not tail)
   3709              (frob "A proper list:" list))
   3710             (t
   3711              (frob "An improper list:" list))))))
   3712 
   3713 (defun inspect-list-aux (list)
   3714   (loop for i from 0  for rest on list  while (consp rest)  append
   3715         (if (listp (cdr rest))
   3716             (label-value-line i (car rest))
   3717             (label-value-line* (i (car rest)) (:tail (cdr rest))))))
   3718 
   3719 (defun safe-length (list)
   3720   "Similar to `list-length', but avoid errors on improper lists.
   3721 Return two values: the length of the list and the last cdr.
   3722 Return NIL if LIST is circular."
   3723   (do ((n 0 (+ n 2))                    ;Counter.
   3724        (fast list (cddr fast))          ;Fast pointer: leaps by 2.
   3725        (slow list (cdr slow)))          ;Slow pointer: leaps by 1.
   3726       (nil)
   3727     (cond ((null fast) (return (values n nil)))
   3728           ((not (consp fast)) (return (values n fast)))
   3729           ((null (cdr fast)) (return (values (1+ n) (cdr fast))))
   3730           ((and (eq fast slow) (> n 0)) (return nil))
   3731           ((not (consp (cdr fast))) (return (values (1+ n) (cdr fast)))))))
   3732 
   3733 ;;;;; Hashtables
   3734 
   3735 (defun hash-table-to-alist (ht)
   3736   (let ((result '()))
   3737     (maphash (lambda (key value)
   3738                (setq result (acons key value result)))
   3739              ht)
   3740     result))
   3741 
   3742 (defmethod emacs-inspect ((ht hash-table))
   3743   (append
   3744    (label-value-line*
   3745     ("Count" (hash-table-count ht))
   3746     ("Size" (hash-table-size ht))
   3747     ("Test" (hash-table-test ht))
   3748     ("Rehash size" (hash-table-rehash-size ht))
   3749     ("Rehash threshold" (hash-table-rehash-threshold ht)))
   3750    (let ((weakness (hash-table-weakness ht)))
   3751      (when weakness
   3752        (label-value-line "Weakness:" weakness)))
   3753    (unless (zerop (hash-table-count ht))
   3754      `((:action "[clear hashtable]"
   3755                 ,(lambda () (clrhash ht))) (:newline)
   3756        "Contents: " (:newline)))
   3757    (let ((content (hash-table-to-alist ht)))
   3758      (cond ((every (lambda (x) (typep (first x) '(or string symbol))) content)
   3759             (setf content (sort content 'string< :key #'first)))
   3760            ((every (lambda (x) (typep (first x) 'real)) content)
   3761             (setf content (sort content '< :key #'first))))
   3762      (loop for (key . value) in content appending
   3763            `((:value ,key) " = " (:value ,value)
   3764              " " (:action "[remove entry]"
   3765                           ,(let ((key key))
   3766                                 (lambda () (remhash key ht))))
   3767              (:newline))))))
   3768 
   3769 ;;;;; Arrays
   3770 
   3771 (defmethod emacs-inspect ((array array))
   3772   (lcons*
   3773    (iline "Dimensions" (array-dimensions array))
   3774    (iline "Element type" (array-element-type array))
   3775    (iline "Total size" (array-total-size array))
   3776    (iline "Adjustable" (adjustable-array-p array))
   3777    (iline "Fill pointer" (if (array-has-fill-pointer-p array)
   3778                              (fill-pointer array)))
   3779    "Contents:" '(:newline)
   3780    (labels ((k (i max)
   3781               (cond ((= i max) '())
   3782                     (t (lcons (iline i (row-major-aref array i))
   3783                               (k (1+ i) max))))))
   3784      (k 0 (array-total-size array)))))
   3785 
   3786 ;;;;; Chars
   3787 
   3788 (defmethod emacs-inspect :around (object)
   3789   (declare (ignore object))
   3790   (with-bindings (if (inspector-verbose-p (current-inspector))
   3791                      *inspector-verbose-printer-bindings*
   3792                      *inspector-printer-bindings*)
   3793     (call-next-method)))
   3794 
   3795 (defmethod emacs-inspect ((char character))
   3796   (append
   3797    (label-value-line*
   3798     ("Char code" (char-code char))
   3799     ("Lower cased" (char-downcase char))
   3800     ("Upper cased" (char-upcase char)))
   3801    (if (get-macro-character char)
   3802        `("In the current readtable ("
   3803          (:value ,*readtable*) ") it is a macro character: "
   3804          (:value ,(get-macro-character char))))))
   3805 
   3806 ;;;; Thread listing
   3807 
   3808 (defvar *thread-list* ()
   3809   "List of threads displayed in Emacs.  We don't care a about
   3810 synchronization issues (yet).  There can only be one thread listing at
   3811 a time.")
   3812 
   3813 (defslyfun list-threads ()
   3814   "Return a list (LABELS (ID NAME STATUS ATTRS ...) ...).
   3815 LABELS is a list of attribute names and the remaining lists are the
   3816 corresponding attribute values per thread.
   3817 Example:
   3818   ((:id :name :status :priority)
   3819    (6 \"slynk-indentation-cache-thread\" \"Semaphore timed wait\" 0)
   3820    (5 \"reader-thread\" \"Active\" 0)
   3821    (4 \"control-thread\" \"Semaphore timed wait\" 0)
   3822    (2 \"Slynk Sentinel\" \"Semaphore timed wait\" 0)
   3823    (1 \"listener\" \"Active\" 0)
   3824    (0 \"Initial\" \"Sleep\" 0))"
   3825   (setq *thread-list* (all-threads))
   3826   (when (and *emacs-connection*
   3827              (use-threads-p)
   3828              ;; FIXME: hardcoded thread name
   3829              (equalp (thread-name (current-thread)) "slynk-worker")) 
   3830     (setf *thread-list* (delete (current-thread) *thread-list*)))
   3831   (let* ((plist (thread-attributes (car *thread-list*)))
   3832          (labels (loop for (key) on plist by #'cddr
   3833                        collect key)))
   3834     `((:id :name :status ,@labels)
   3835       ,@(loop for thread in *thread-list*
   3836               for name = (thread-name thread)
   3837               for attributes = (thread-attributes thread)
   3838               collect (list* (thread-id thread)
   3839                              (string name)
   3840                              (thread-status thread)
   3841                              (loop for label in labels
   3842                                    collect (getf attributes label)))))))
   3843 
   3844 (defslyfun quit-thread-browser ()
   3845   (setq *thread-list* nil))
   3846 
   3847 (defun nth-thread (index)
   3848   (nth index *thread-list*))
   3849 
   3850 (defslyfun debug-nth-thread (index)
   3851   (let ((connection *emacs-connection*))
   3852     (queue-thread-interrupt
   3853      (nth-thread index)
   3854      (lambda ()
   3855        (with-connection (connection)
   3856          (simple-break))))))
   3857 
   3858 (defslyfun kill-nth-thread (index)
   3859   (kill-thread (nth-thread index)))
   3860 
   3861 (defslyfun start-slynk-server-in-thread (index port-file-name)
   3862   "Interrupt the INDEXth thread and make it start a slynk server.
   3863 The server port is written to PORT-FILE-NAME."
   3864   (interrupt-thread (nth-thread index)
   3865                     (lambda ()
   3866                       (start-server port-file-name :style nil))))
   3867 
   3868 ;;;; Class browser
   3869 
   3870 (defun mop-helper (class-name fn)
   3871   (let ((class (find-class class-name nil)))
   3872     (if class
   3873         (mapcar (lambda (x) (to-string (class-name x)))
   3874                 (funcall fn class)))))
   3875 
   3876 (defslyfun mop (type symbol-name)
   3877   "Return info about classes using mop.
   3878 
   3879     When type is:
   3880      :subclasses - return the list of subclasses of class.
   3881      :superclasses - return the list of superclasses of class."
   3882   (let ((symbol (parse-symbol symbol-name *buffer-package*)))
   3883     (ecase type
   3884       (:subclasses
   3885        (mop-helper symbol #'slynk-mop:class-direct-subclasses))
   3886       (:superclasses
   3887        (mop-helper symbol #'slynk-mop:class-direct-superclasses)))))
   3888 
   3889 
   3890 ;;;; Automatically synchronized state
   3891 ;;;
   3892 ;;; Here we add hooks to push updates of relevant information to
   3893 ;;; Emacs.
   3894 
   3895 ;;;;; *FEATURES*
   3896 
   3897 (defun sync-features-to-emacs ()
   3898   "Update Emacs if any relevant Lisp state has changed."
   3899   ;; FIXME: *sly-features* should be connection-local
   3900   (unless (eq *sly-features* *features*)
   3901     (setq *sly-features* *features*)
   3902     (send-to-emacs (list :new-features (features-for-emacs)))))
   3903 
   3904 (defun features-for-emacs ()
   3905   "Return `*sly-features*' in a format suitable to send it to Emacs."
   3906   *sly-features*)
   3907 
   3908 (add-hook *pre-reply-hook* 'sync-features-to-emacs)
   3909 
   3910 
   3911 ;;;;; Indentation of macros
   3912 ;;;
   3913 ;;; This code decides how macros should be indented (based on their
   3914 ;;; arglists) and tells Emacs. A per-connection cache is used to avoid
   3915 ;;; sending redundant information to Emacs -- we just say what's
   3916 ;;; changed since last time.
   3917 ;;;
   3918 ;;; The strategy is to scan all symbols, pick out the macros, and look
   3919 ;;; for &body-arguments.
   3920 
   3921 (defvar *configure-emacs-indentation* t
   3922   "When true, automatically send indentation information to Emacs
   3923 after each command.")
   3924 
   3925 (defslyfun update-indentation-information ()
   3926   (send-to-indentation-cache `(:update-indentation-information))
   3927   nil)
   3928 
   3929 ;; This function is for *PRE-REPLY-HOOK*.
   3930 (defun sync-indentation-to-emacs ()
   3931   "Send any indentation updates to Emacs via CONNECTION."
   3932   (when *configure-emacs-indentation*
   3933     (send-to-indentation-cache `(:sync-indentation ,*buffer-package*))))
   3934 
   3935 ;; Send REQUEST to the cache.  If we are single threaded perform the
   3936 ;; request right away, otherwise delegate the request to the
   3937 ;; indentation-cache-thread.
   3938 (defun send-to-indentation-cache (request)
   3939   (let ((c *emacs-connection*))
   3940     (etypecase c
   3941       (singlethreaded-connection
   3942        (handle-indentation-cache-request c request))
   3943       (multithreaded-connection
   3944        (without-sly-interrupts
   3945          (send (mconn.indentation-cache-thread c) request)))
   3946       (null t))))
   3947 
   3948 (defun indentation-cache-loop (connection)
   3949   (with-connection (connection)
   3950     (loop
   3951       (restart-case
   3952           (handle-indentation-cache-request connection (receive))
   3953         (abort ()
   3954           :report "Return to the indentation cache request handling loop.")))))
   3955 
   3956 (defun handle-indentation-cache-request (connection request)
   3957   (destructure-case request
   3958     ((:sync-indentation package)
   3959      ;; PACKAGE may have been deleted...
   3960      (when (package-name package)
   3961        (let ((fullp (need-full-indentation-update-p connection)))
   3962          (perform-indentation-update connection fullp package))))
   3963     ((:update-indentation-information)
   3964      (perform-indentation-update connection t nil))))
   3965 
   3966 (defun need-full-indentation-update-p (connection)
   3967   "Return true if the whole indentation cache should be updated.
   3968 This is a heuristic to avoid scanning all symbols all the time:
   3969 instead, we only do a full scan if the set of packages has changed."
   3970   (set-difference (list-all-packages)
   3971                   (connection-indentation-cache-packages connection)))
   3972 
   3973 (defun perform-indentation-update (connection force package)
   3974   "Update the indentation cache in CONNECTION and update Emacs.
   3975 If FORCE is true then start again without considering the old cache."
   3976   (let ((cache (connection-indentation-cache connection)))
   3977     (when force (clrhash cache))
   3978     (let ((delta (update-indentation/delta-for-emacs cache force package)))
   3979       (setf (connection-indentation-cache-packages connection)
   3980             (list-all-packages))
   3981       (unless (null delta)
   3982         (setf (connection-indentation-cache connection) cache)
   3983         (send-to-emacs (list :indentation-update delta))))))
   3984 
   3985 (defun update-indentation/delta-for-emacs (cache force package)
   3986   "Update the cache and return the changes in a (SYMBOL INDENT PACKAGES) list.
   3987 If FORCE is true then check all symbols, otherwise only check symbols
   3988 belonging to PACKAGE."
   3989   (let ((alist '()))
   3990     (flet ((consider (symbol)
   3991              (let ((indent (symbol-indentation symbol)))
   3992                (when indent
   3993                  (unless (equal (gethash symbol cache) indent)
   3994                    (setf (gethash symbol cache) indent)
   3995                    (let ((pkgs (mapcar #'package-name
   3996                                        (symbol-packages symbol)))
   3997                          (name (string-downcase symbol)))
   3998                      (push (list name indent pkgs) alist)))))))
   3999       (cond (force
   4000              (do-all-symbols (symbol)
   4001                (consider symbol)))
   4002             ((package-name package) ; don't try to iterate over a
   4003                                     ; deleted package.
   4004              (do-symbols (symbol package)
   4005                (when (eq (symbol-package symbol) package)
   4006                  (consider symbol)))))
   4007       alist)))
   4008 
   4009 (defun package-names (package)
   4010   "Return the name and all nicknames of PACKAGE in a fresh list."
   4011   (cons (package-name package) (copy-list (package-nicknames package))))
   4012 
   4013 (defun symbol-packages (symbol)
   4014   "Return the  packages where SYMBOL can be found."
   4015   (let ((string (string symbol)))
   4016     (loop for p in (list-all-packages)
   4017           when (eq symbol (find-symbol string p))
   4018           collect p)))
   4019 
   4020 (defun cl-symbol-p (symbol)
   4021   "Is SYMBOL a symbol in the COMMON-LISP package?"
   4022   (eq (symbol-package symbol) cl-package))
   4023 
   4024 (defun known-to-emacs-p (symbol)
   4025   "Return true if Emacs has special rules for indenting SYMBOL."
   4026   (cl-symbol-p symbol))
   4027 
   4028 (defun symbol-indentation (symbol)
   4029   "Return a form describing the indentation of SYMBOL.
   4030 The form is to be used as the `sly-common-lisp-indent-function' property
   4031 in Emacs."
   4032   (if (and (macro-function symbol)
   4033            (not (known-to-emacs-p symbol)))
   4034       (let ((arglist (arglist symbol)))
   4035         (etypecase arglist
   4036           ((member :not-available)
   4037            nil)
   4038           (list
   4039            (macro-indentation arglist))))
   4040       nil))
   4041 
   4042 (defun macro-indentation (arglist)
   4043   (if (well-formed-list-p arglist)
   4044       (position '&body (remove '&optional (clean-arglist arglist)))
   4045       nil))
   4046 
   4047 (defun clean-arglist (arglist)
   4048   "Remove &whole, &enviroment, and &aux elements from ARGLIST."
   4049   (cond ((null arglist) '())
   4050         ((member (car arglist) '(&whole &environment))
   4051          (clean-arglist (cddr arglist)))
   4052         ((eq (car arglist) '&aux)
   4053          '())
   4054         (t (cons (car arglist) (clean-arglist (cdr arglist))))))
   4055 
   4056 (defun well-formed-list-p (list)
   4057   "Is LIST a proper list terminated by NIL?"
   4058   (typecase list
   4059     (null t)
   4060     (cons (well-formed-list-p (cdr list)))
   4061     (t    nil)))
   4062 
   4063 (defun print-indentation-lossage (&optional (stream *standard-output*))
   4064   "Return the list of symbols whose indentation styles collide incompatibly.
   4065 Collisions are caused because package information is ignored."
   4066   (let ((table (make-hash-table :test 'equal)))
   4067     (flet ((name (s) (string-downcase (symbol-name s))))
   4068       (do-all-symbols (s)
   4069         (setf (gethash (name s) table)
   4070               (cons s (symbol-indentation s))))
   4071       (let ((collisions '()))
   4072         (do-all-symbols (s)
   4073           (let* ((entry (gethash (name s) table))
   4074                  (owner (car entry))
   4075                  (indent (cdr entry)))
   4076             (unless (or (eq s owner)
   4077                         (equal (symbol-indentation s) indent)
   4078                         (and (not (fboundp s))
   4079                              (null (macro-function s))))
   4080               (pushnew owner collisions)
   4081               (pushnew s collisions))))
   4082         (if (null collisions)
   4083             (format stream "~&No worries!~%")
   4084             (format stream "~&Symbols with collisions:~%~{  ~S~%~}"
   4085                     collisions))))))
   4086 
   4087 ;;; FIXME: it's too slow on CLASP right now, remove once it's fast enough.
   4088 #-clasp
   4089 (add-hook *pre-reply-hook* 'sync-indentation-to-emacs)
   4090 
   4091 
   4092 ;;;; Testing
   4093 
   4094 (defslyfun io-speed-test (&optional (n 1000) (m 1))
   4095   (let* ((s *standard-output*)
   4096          (*trace-output* (make-broadcast-stream s *log-output*)))
   4097     (time (progn
   4098             (dotimes (i n)
   4099               (format s "~D abcdefghijklm~%" i)
   4100               (when (zerop (mod n m))
   4101                 (finish-output s)))
   4102             (finish-output s)
   4103             (when *emacs-connection*
   4104               (eval-in-emacs '(message "done.")))))
   4105     (terpri *trace-output*)
   4106     (finish-output *trace-output*)
   4107     nil))
   4108 
   4109 (defslyfun flow-control-test (n delay)
   4110   (let ((stream (make-output-stream
   4111                  (let ((conn *emacs-connection*))
   4112                    (lambda (string)
   4113                      (declare (ignore string))
   4114                      (with-connection (conn)
   4115                        (send-to-emacs `(:test-delay ,delay))))))))
   4116     (dotimes (i n)
   4117       (print i stream)
   4118       (force-output stream)
   4119       (background-message "flow-control-test: ~d" i))))
   4120 
   4121 
   4122 ;;;; The "official" API
   4123 
   4124 (defpackage :slynk-api (:use))
   4125 (eval-when (:compile-toplevel :load-toplevel :execute)
   4126   (let ((api '(#:*emacs-connection*
   4127                #:*m-x-sly-from-emacs*
   4128                #:default-connection
   4129                ;;
   4130                #:channel
   4131                #:channel-id
   4132                #:channel-thread-id
   4133                #:close-channel
   4134                #:define-channel-method
   4135                #:find-channel
   4136                #:send-to-remote-channel
   4137                #:*channel*
   4138                ;;
   4139                #:listener
   4140                #:with-listener-bindings
   4141                #:saving-listener-bindings
   4142                #:flush-listener-streams
   4143                #:default-listener
   4144                #:close-listener
   4145                ;;
   4146                #:add-hook
   4147                #:*connection-closed-hook*
   4148                #:*after-init-hook*
   4149                #:*new-connection-hook*
   4150                #:*pre-reply-hook*
   4151                #:*after-toggle-trace-hook*
   4152                #:*eval-for-emacs-wrappers*
   4153                #:*debugger-extra-options*
   4154                #:*buffer-readtable*
   4155                ;;
   4156                #:defslyfun
   4157                #:destructure-case
   4158                #:log-event
   4159                #:process-requests
   4160                #:use-threads-p
   4161                #:wait-for-event
   4162                #:with-bindings
   4163                #:with-connection
   4164                #:with-top-level-restart
   4165                #:with-sly-interrupts
   4166                #:with-buffer-syntax
   4167                #:with-retry-restart
   4168                #:*loaded-user-init-file*
   4169                #:load-user-init-file
   4170                #:make-thread-bindings-aware-lambda
   4171                ;;
   4172                #:package-string-for-prompt
   4173                ;;
   4174                #:*slynk-wire-protocol-version*
   4175                ;;
   4176                #:*slynk-require-hook*
   4177                ;;
   4178                #:present-for-emacs
   4179                ;; packages
   4180                ;;
   4181                #:cl-package
   4182                #:+keyword-package+
   4183                #:guess-package
   4184                #:guess-buffer-package
   4185                #:*exclude-symbol-functions*
   4186                #:*buffer-package*
   4187                #:*slynk-io-package*
   4188                #:parse-package
   4189                ;; symbols
   4190                ;;
   4191                #:tokenize-symbol
   4192                #:untokenize-symbol
   4193                #:symbol-external-p
   4194                #:unparse-name
   4195                #:excluded-from-searches-p
   4196                ;;
   4197                ;;
   4198                #:slynk-pprint
   4199                #:slynk-pprint-values
   4200                #:slynk-pprint-to-line
   4201                ;;
   4202                ;;
   4203                #:background-message
   4204                #:map-if)))
   4205     (loop for sym in api
   4206           for slynk-api-sym = (intern (string sym) :slynk-api)
   4207           for slynk-sym = (intern (string sym) :slynk)
   4208           do (unintern slynk-api-sym :slynk-api)
   4209              (import slynk-sym :slynk-api)
   4210              (export slynk-sym :slynk-api))))
   4211 
   4212 
   4213 ;;;; INIT, as called from the slynk-loader.lisp and ASDF's loaders
   4214 ;;;;
   4215 (defvar *loaded-user-init-file* nil
   4216   "User init file actually loaded from user's home, if any.")
   4217 (defun load-user-init-file ()
   4218   "Load the user init file, return NIL if it does not exist."
   4219   (find-if (lambda (homedir-file)
   4220              (load (merge-pathnames (user-homedir-pathname)
   4221                                     homedir-file)
   4222                    :if-does-not-exist nil))
   4223            (list (make-pathname :name ".slynk" :type "lisp")
   4224                  (make-pathname :name ".slynkrc"))))
   4225 
   4226 (defun init ()
   4227   (unless (member :slynk *features*)
   4228     (pushnew :slynk *features*))
   4229   (setq *loaded-user-init-file* (load-user-init-file))
   4230   (run-hook *after-init-hook*))
   4231 
   4232 ;; Local Variables:
   4233 ;; sly-load-failed-fasl: ask
   4234 ;; End: