dotemacs

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

slynk.lisp (158811B)


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