dotemacs

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

slynk-backend.lisp (60200B)


      1 ;;; -*- indent-tabs-mode: nil; outline-regexp: ";;;;;*" -*-
      2 ;;;
      3 ;;; sly-backend.lisp --- SLY backend interface.
      4 ;;;
      5 ;;; Created by James Bielman in 2003. Released into the public domain.
      6 ;;;
      7 ;;;; Frontmatter
      8 ;;;
      9 ;;; This file defines the functions that must be implemented
     10 ;;; separately for each Lisp. Each is declared as a generic function
     11 ;;; for which slynk-<implementation>.lisp provides methods.
     12 
     13 (defpackage slynk-backend
     14   (:use cl)
     15   (:export *debug-slynk-backend*
     16            sly-db-condition
     17            compiler-condition
     18            original-condition
     19            message
     20            source-context
     21            condition
     22            severity
     23            with-compilation-hooks
     24            make-location
     25            location
     26            location-p
     27            location-buffer
     28            location-position
     29 	   location-hints
     30            position-p
     31            position-pos
     32            print-output-to-string
     33            quit-lisp
     34            references
     35            unbound-slot-filler
     36            declaration-arglist
     37            type-specifier-arglist
     38            with-struct
     39            when-let
     40 	   defimplementation
     41 	   converting-errors-to-error-location
     42 	   make-error-location
     43 	   deinit-log-output
     44            ;; interrupt macro for the backend
     45            *pending-sly-interrupts*
     46            check-sly-interrupts
     47            *interrupt-queued-handler*
     48            ;; inspector related symbols
     49            emacs-inspect
     50            label-value-line
     51            label-value-line*
     52            with-symbol
     53            choose-symbol
     54            boolean-to-feature-expression
     55            ;; package helper for backend
     56            import-to-slynk-mop
     57            import-slynk-mop-symbols
     58 	   ;;
     59            definterface
     60            defimplementation
     61            ;; auto-flush
     62            auto-flush-loop
     63            *auto-flush-interval*
     64            ))
     65 
     66 (defpackage slynk-mop
     67   (:use)
     68   (:export
     69    ;; classes
     70    standard-generic-function
     71    standard-slot-definition
     72    standard-method
     73    standard-class
     74    eql-specializer
     75    eql-specializer-object
     76    ;; standard-class readers
     77    class-default-initargs
     78    class-direct-default-initargs
     79    class-direct-slots
     80    class-direct-subclasses
     81    class-direct-superclasses
     82    class-finalized-p
     83    class-name
     84    class-precedence-list
     85    class-prototype
     86    class-slots
     87    specializer-direct-methods
     88    ;; generic function readers
     89    generic-function-argument-precedence-order
     90    generic-function-declarations
     91    generic-function-lambda-list
     92    generic-function-methods
     93    generic-function-method-class
     94    generic-function-method-combination
     95    generic-function-name
     96    ;; method readers
     97    method-generic-function
     98    method-function
     99    method-lambda-list
    100    method-specializers
    101    method-qualifiers
    102    ;; slot readers
    103    slot-definition-allocation
    104    slot-definition-documentation
    105    slot-definition-initargs
    106    slot-definition-initform
    107    slot-definition-initfunction
    108    slot-definition-name
    109    slot-definition-type
    110    slot-definition-readers
    111    slot-definition-writers
    112    slot-boundp-using-class
    113    slot-value-using-class
    114    slot-makunbound-using-class
    115    ;; generic function protocol
    116    compute-applicable-methods-using-classes
    117    finalize-inheritance))
    118 
    119 (in-package slynk-backend)
    120 
    121 
    122 ;;;; Metacode
    123 
    124 (defparameter *debug-slynk-backend* nil
    125   "If this is true, backends should not catch errors but enter the
    126 debugger where appropriate. Also, they should not perform backtrace
    127 magic but really show every frame including SLYNK related ones.")
    128 
    129 (defparameter *interface-functions* '()
    130   "The names of all interface functions.")
    131 
    132 (defparameter *unimplemented-interfaces* '()
    133   "List of interface functions that are not implemented.
    134 DEFINTERFACE adds to this list and DEFIMPLEMENTATION removes.")
    135 
    136 (defmacro definterface (name args documentation &rest default-body)
    137   "Define an interface function for the backend to implement.
    138 A function is defined with NAME, ARGS, and DOCUMENTATION.  This
    139 function first looks for a function to call in NAME's property list
    140 that is indicated by 'IMPLEMENTATION; failing that, it looks for a
    141 function indicated by 'DEFAULT. If neither is present, an error is
    142 signaled.
    143 
    144 If a DEFAULT-BODY is supplied, then a function with the same body and
    145 ARGS will be added to NAME's property list as the property indicated
    146 by 'DEFAULT.
    147 
    148 Backends implement these functions using DEFIMPLEMENTATION."
    149   (check-type documentation string "a documentation string")
    150   (assert (every #'symbolp args) ()
    151           "Complex lambda-list not supported: ~S ~S" name args)
    152   (labels ((gen-default-impl ()
    153              `(setf (get ',name 'default) (lambda ,args ,@default-body)))
    154            (args-as-list (args)
    155              (destructuring-bind (req opt key rest) (parse-lambda-list args)
    156                `(,@req ,@opt
    157                        ,@(loop for k in key append `(,(kw k) ,k))
    158                        ,@(or rest '(())))))
    159            (parse-lambda-list (args)
    160              (parse args '(&optional &key &rest)
    161                     (make-array 4 :initial-element nil)))
    162            (parse (args keywords vars)
    163              (cond ((null args)
    164                     (reverse (map 'list #'reverse vars)))
    165                    ((member (car args) keywords)
    166                     (parse (cdr args) (cdr (member (car args) keywords)) vars))
    167                    (t (push (car args) (aref vars (length keywords)))
    168                       (parse (cdr args) keywords vars))))
    169            (kw (s) (intern (string s) :keyword)))
    170     `(progn
    171        (defun ,name ,args
    172          ,documentation
    173          (let ((f (or (get ',name 'implementation)
    174                       (get ',name 'default))))
    175            (cond (f (apply f ,@(args-as-list args)))
    176                  (t (error "~S not implemented" ',name)))))
    177        (pushnew ',name *interface-functions*)
    178        ,(if (null default-body)
    179             `(pushnew ',name *unimplemented-interfaces*)
    180             (gen-default-impl))
    181        (eval-when (:compile-toplevel :load-toplevel :execute)
    182          (import ',name :slynk-backend)
    183          (export ',name :slynk-backend))
    184        ',name)))
    185 
    186 (defmacro defimplementation (name args &body body)
    187   (assert (every #'symbolp args) ()
    188           "Complex lambda-list not supported: ~S ~S" name args)
    189   (let ((sym (find-symbol (symbol-name name) :slynk-backend)))
    190     `(progn
    191        (setf (get ',sym 'implementation)
    192              ;; For implicit BLOCK. FLET because of interplay w/ decls.
    193              (flet ((,sym ,args ,@body)) #',sym))
    194        (if (member ',sym *interface-functions*)
    195            (setq *unimplemented-interfaces*
    196                  (remove ',sym *unimplemented-interfaces*))
    197            (warn "DEFIMPLEMENTATION of undefined interface (~S)" ',sym))
    198        ',sym)))
    199 
    200 (defun warn-unimplemented-interfaces ()
    201   "Warn the user about unimplemented backend features.
    202 The portable code calls this function at startup."
    203   (let ((*print-pretty* t))
    204     (warn "These Slynk interfaces are unimplemented:~% ~:<~{~A~^ ~:_~}~:>"
    205           (list (sort (copy-list *unimplemented-interfaces*) #'string<)))))
    206 
    207 (defun import-to-slynk-mop (symbol-list)
    208   (dolist (sym symbol-list)
    209     (let* ((slynk-mop-sym (find-symbol (symbol-name sym) :slynk-mop)))
    210       (when slynk-mop-sym
    211         (unintern slynk-mop-sym :slynk-mop))
    212       (import sym :slynk-mop)
    213       (export sym :slynk-mop))))
    214 
    215 (defun import-slynk-mop-symbols (package except)
    216   "Import the mop symbols from PACKAGE to SLYNK-MOP.
    217 EXCEPT is a list of symbol names which should be ignored."
    218   (do-symbols (s :slynk-mop)
    219     (unless (member s except :test #'string=)
    220       (let ((real-symbol (find-symbol (string s) package)))
    221         (assert real-symbol () "Symbol ~A not found in package ~A" s package)
    222         (unintern s :slynk-mop)
    223         (import real-symbol :slynk-mop)
    224         (export real-symbol :slynk-mop)))))
    225 
    226 (definterface gray-package-name ()
    227   "Return a package-name that contains the Gray stream symbols.
    228 This will be used like so:
    229   (defpackage foo
    230     (:import-from #.(gray-package-name) . #.*gray-stream-symbols*)")
    231 
    232 
    233 ;;;; Utilities
    234 
    235 (defmacro with-struct ((conc-name &rest names) obj &body body)
    236   "Like with-slots but works only for structs."
    237   (check-type conc-name symbol)
    238   (flet ((reader (slot)
    239            (intern (concatenate 'string
    240                                 (symbol-name conc-name)
    241                                 (symbol-name slot))
    242                    (symbol-package conc-name))))
    243     (let ((tmp (gensym "OO-")))
    244       ` (let ((,tmp ,obj))
    245           (symbol-macrolet
    246               ,(loop for name in names collect
    247                      (typecase name
    248                        (symbol `(,name (,(reader name) ,tmp)))
    249                        (cons `(,(first name) (,(reader (second name)) ,tmp)))
    250                        (t (error "Malformed syntax in WITH-STRUCT: ~A" name))))
    251             ,@body)))))
    252 
    253 (defmacro when-let ((var value) &body body)
    254   `(let ((,var ,value))
    255      (when ,var ,@body)))
    256 
    257 (defun boolean-to-feature-expression (value)
    258   "Converts a boolean VALUE to a form suitable for testing with #+."
    259   (if value
    260       '(:and)
    261       '(:or)))
    262 
    263 (defun with-symbol (name package)
    264   "Check if a symbol with a given NAME exists in PACKAGE and returns a
    265 form suitable for testing with #+."
    266   (boolean-to-feature-expression
    267    (and (find-package package)
    268         (find-symbol (string name) package))))
    269 
    270 (defun choose-symbol (package name alt-package alt-name)
    271   "If symbol package:name exists return that symbol, otherwise alt-package:alt-name.
    272   Suitable for use with #."
    273   (or (and (find-package package)
    274            (find-symbol (string name) package))
    275       (find-symbol (string alt-name) alt-package)))
    276 
    277 
    278 ;;;; UFT8
    279 
    280 (deftype octet () '(unsigned-byte 8))
    281 (deftype octets () '(simple-array octet (*)))
    282 
    283 ;; Helper function.  Decode the next N bytes starting from INDEX.
    284 ;; Return the decoded char and the new index.
    285 (defun utf8-decode-aux (buffer index limit byte0 n)
    286   (declare (type octets buffer) (fixnum index limit byte0 n))
    287   (if (< (- limit index) n)
    288       (values nil index)
    289       (do ((i 0 (1+ i))
    290            (code byte0 (let ((byte (aref buffer (+ index i))))
    291                          (cond ((= (ldb (byte 2 6) byte) #b10)
    292                                 (+ (ash code 6) (ldb (byte 6 0) byte)))
    293                                (t
    294                                 #xFFFD))))) ;; Replacement_Character
    295           ((= i n)
    296            (values (cond ((<= code #xff) (code-char code))
    297                          ((<= #xd800 code #xdfff)
    298                           (code-char #xFFFD)) ;; Replacement_Character
    299                          ((and (< code char-code-limit)
    300                                (code-char code)))
    301                          (t
    302                           (code-char #xFFFD))) ;; Replacement_Character
    303                    (+ index n))))))
    304 
    305 ;; Decode one character in BUFFER starting at INDEX.
    306 ;; Return 2 values: the character and the new index.
    307 ;; If there aren't enough bytes between INDEX and LIMIT return nil.
    308 (defun utf8-decode (buffer index limit)
    309   (declare (type octets buffer) (fixnum index limit))
    310   (if (= index limit)
    311       (values nil index)
    312       (let ((b (aref buffer index)))
    313         (if (<= b #x7f)
    314             (values (code-char b) (1+ index))
    315             (macrolet ((try (marker else)
    316                          (let* ((l (integer-length marker))
    317                                 (n (- l 2)))
    318                            `(if (= (ldb (byte ,l ,(- 8 l)) b) ,marker)
    319                                 (utf8-decode-aux buffer (1+ index) limit
    320                                                  (ldb (byte ,(- 8 l) 0) b)
    321                                                  ,n)
    322                                 ,else))))
    323               (try #b110
    324                    (try #b1110
    325                         (try #b11110
    326                              (try #b111110
    327                                   (try #b1111110
    328                                        (error "Invalid encoding")))))))))))
    329 
    330 ;; Decode characters from BUFFER and write them to STRING.
    331 ;; Return 2 values: LASTINDEX and LASTSTART where
    332 ;; LASTINDEX is the last index in BUFFER that was not decoded
    333 ;; and LASTSTART is the last index in STRING not written.
    334 (defun utf8-decode-into (buffer index limit string start end)
    335   (declare (string string) (fixnum index limit start end) (type octets buffer))
    336   (loop
    337    (cond ((= start end)
    338           (return (values index start)))
    339          (t
    340           (multiple-value-bind (c i) (utf8-decode buffer index limit)
    341             (cond (c
    342                    (setf (aref string start) c)
    343                    (setq index i)
    344                    (setq start (1+ start)))
    345                   (t
    346                    (return (values index start)))))))))
    347 
    348 (defun default-utf8-to-string (octets)
    349   (let* ((limit (length octets))
    350          (str (make-string limit)))
    351     (multiple-value-bind (i s) (utf8-decode-into octets 0 limit str 0 limit)
    352       (if (= i limit)
    353           (if (= limit s)
    354               str
    355               (adjust-array str s))
    356           (loop
    357            (let ((end (+ (length str) (- limit i))))
    358              (setq str (adjust-array str end))
    359              (multiple-value-bind (i2 s2)
    360                  (utf8-decode-into octets i limit str s end)
    361                (cond ((= i2 limit)
    362                       (return (adjust-array str s2)))
    363                      (t
    364                       (setq i i2)
    365                       (setq s s2))))))))))
    366 
    367 (defmacro utf8-encode-aux (code buffer start end n)
    368   `(cond ((< (- ,end ,start) ,n)
    369           ,start)
    370          (t
    371           (setf (aref ,buffer ,start)
    372                 (dpb (ldb (byte ,(- 7 n) ,(* 6 (1- n))) ,code)
    373                      (byte ,(- 7 n) 0)
    374                      ,(dpb 0 (byte 1 (- 7 n)) #xff)))
    375           ,@(loop for i from 0 upto (- n 2) collect
    376                   `(setf (aref ,buffer (+ ,start ,(- n 1 i)))
    377                          (dpb (ldb (byte 6 ,(* 6 i)) ,code)
    378                               (byte 6 0)
    379                               #b10111111)))
    380           (+ ,start ,n))))
    381 
    382 (defun %utf8-encode (code buffer start end)
    383   (declare (type (unsigned-byte 31) code) (type octets buffer)
    384            (type (and fixnum unsigned-byte) start end))
    385   (cond ((<= code #x7f)
    386          (cond ((< start end)
    387                 (setf (aref buffer start) code)
    388                 (1+ start))
    389                (t start)))
    390         ((<= code #x7ff) (utf8-encode-aux code buffer start end 2))
    391         ((<= #xd800 code #xdfff)
    392          (%utf8-encode (code-char #xFFFD) ;; Replacement_Character
    393                        buffer start end))
    394         ((<= code #xffff) (utf8-encode-aux code buffer start end 3))
    395         ((<= code #x1fffff) (utf8-encode-aux code buffer start end 4))
    396         ((<= code #x3ffffff) (utf8-encode-aux code buffer start end 5))
    397         (t (utf8-encode-aux code buffer start end 6))))
    398 
    399 (defun utf8-encode (char buffer start end)
    400   (declare (type character char) (type octets buffer)
    401            (type (and fixnum unsigned-byte) start end))
    402   (%utf8-encode (char-code char) buffer start end))
    403 
    404 (defun utf8-encode-into (string start end buffer index limit)
    405   (declare (string string) (type octets buffer) (fixnum start end index limit))
    406   (loop
    407    (cond ((= start end)
    408           (return (values start index)))
    409          ((= index limit)
    410           (return (values start index)))
    411          (t
    412           (let ((i2 (utf8-encode (char string start) buffer index limit)))
    413             (cond ((= i2 index)
    414                    (return (values start index)))
    415                   (t
    416                    (setq index i2)
    417                    (incf start))))))))
    418 
    419 (defun default-string-to-utf8 (string)
    420   (let* ((len (length string))
    421          (b (make-array len :element-type 'octet)))
    422     (multiple-value-bind (s i) (utf8-encode-into string 0 len b 0 len)
    423       (if (= s len)
    424           b
    425           (loop
    426            (let ((limit (+ (length b) (- len s))))
    427              (setq b (coerce (adjust-array b limit) 'octets))
    428              (multiple-value-bind (s2 i2)
    429                  (utf8-encode-into string s len b i limit)
    430                (cond ((= s2 len)
    431                       (return (coerce (adjust-array b i2) 'octets)))
    432                      (t
    433                       (setq i i2)
    434                       (setq s s2))))))))))
    435 
    436 (definterface string-to-utf8 (string)
    437   "Convert the string STRING to a (simple-array (unsigned-byte 8))"
    438   (default-string-to-utf8 string))
    439 
    440 (definterface utf8-to-string (octets)
    441   "Convert the (simple-array (unsigned-byte 8)) OCTETS to a string."
    442   (default-utf8-to-string octets))
    443 
    444 ;;; Codepoint length
    445 
    446 ;; we don't need this anymore.
    447 (definterface codepoint-length (string)
    448   "Return the number of codepoints in STRING.
    449 With some Lisps, like cmucl, LENGTH returns the number of UTF-16 code
    450 units, but other Lisps return the number of codepoints. The sly
    451 protocol wants string lengths in terms of codepoints."
    452   (length string))
    453 
    454 
    455 ;;;; TCP server
    456 
    457 (definterface create-socket (host port &key backlog)
    458   "Create a listening TCP socket on interface HOST and port PORT.
    459 BACKLOG queue length for incoming connections.")
    460 
    461 (definterface local-port (socket)
    462   "Return the local port number of SOCKET.")
    463 
    464 (definterface close-socket (socket)
    465   "Close the socket SOCKET.")
    466 
    467 (definterface accept-connection (socket &key external-format
    468                                         buffering timeout)
    469    "Accept a client connection on the listening socket SOCKET.
    470 Return a stream for the new connection.
    471 If EXTERNAL-FORMAT is nil return a binary stream
    472 otherwise create a character stream.
    473 BUFFERING can be one of:
    474   nil   ... no buffering
    475   t     ... enable buffering
    476   :line ... enable buffering with automatic flushing on eol.")
    477 
    478 (definterface add-sigio-handler (socket fn)
    479   "Call FN whenever SOCKET is readable.")
    480 
    481 (definterface remove-sigio-handlers (socket)
    482   "Remove all sigio handlers for SOCKET.")
    483 
    484 (definterface add-fd-handler (socket fn)
    485   "Call FN when Lisp is waiting for input and SOCKET is readable.")
    486 
    487 (definterface remove-fd-handlers (socket)
    488   "Remove all fd-handlers for SOCKET.")
    489 
    490 (definterface preferred-communication-style ()
    491   "Return one of the symbols :spawn, :sigio, :fd-handler, or NIL."
    492   nil)
    493 
    494 (definterface set-stream-timeout (stream timeout)
    495   "Set the 'stream 'timeout.  The timeout is either the real number
    496   specifying the timeout in seconds or 'nil for no timeout."
    497   (declare (ignore stream timeout))
    498   nil)
    499 
    500 ;;; Base condition for networking errors.
    501 (define-condition network-error (simple-error) ())
    502 
    503 (definterface emacs-connected ()
    504    "Hook called when the first connection from Emacs is established.
    505 Called from the INIT-FN of the socket server that accepts the
    506 connection.
    507 
    508 This is intended for setting up extra context, e.g. to discover
    509 that the calling thread is the one that interacts with Emacs."
    510    nil)
    511 
    512 
    513 ;;;; Unix signals
    514 
    515 (defconstant +sigint+ 2)
    516 
    517 (definterface getpid ()
    518   "Return the (Unix) process ID of this superior Lisp.")
    519 
    520 (definterface install-sigint-handler (function)
    521   "Call FUNCTION on SIGINT (instead of invoking the debugger).
    522 Return old signal handler."
    523   (declare (ignore function))
    524   nil)
    525 
    526 (definterface call-with-user-break-handler (handler function)
    527   "Install the break handler HANDLER while executing FUNCTION."
    528   (let ((old-handler (install-sigint-handler handler)))
    529     (unwind-protect (funcall function)
    530       (install-sigint-handler old-handler))))
    531 
    532 (definterface quit-lisp ()
    533   "Exit the current lisp image.")
    534 
    535 (definterface lisp-implementation-type-name ()
    536   "Return a short name for the Lisp implementation."
    537   (lisp-implementation-type))
    538 
    539 (definterface lisp-implementation-program ()
    540   "Return the argv[0] of the running Lisp process, or NIL."
    541   (let ((file (car (command-line-args))))
    542     (when (and file (probe-file file))
    543       (namestring (truename file)))))
    544 
    545 (definterface socket-fd (socket-stream)
    546   "Return the file descriptor for SOCKET-STREAM.")
    547 
    548 (definterface make-fd-stream (fd external-format)
    549   "Create a character stream for the file descriptor FD.")
    550 
    551 (definterface dup (fd)
    552   "Duplicate a file descriptor.
    553 If the syscall fails, signal a condition.
    554 See dup(2).")
    555 
    556 (definterface exec-image (image-file args)
    557   "Replace the current process with a new process image.
    558 The new image is created by loading the previously dumped
    559 core file IMAGE-FILE.
    560 ARGS is a list of strings passed as arguments to
    561 the new image.
    562 This is thin wrapper around exec(3).")
    563 
    564 (definterface command-line-args ()
    565   "Return a list of strings as passed by the OS."
    566   nil)
    567 
    568 
    569 ;; pathnames are sooo useless
    570 
    571 (definterface filename-to-pathname (filename)
    572   "Return a pathname for FILENAME.
    573 A filename in Emacs may for example contain asterisks which should not
    574 be translated to wildcards."
    575   (parse-namestring filename))
    576 
    577 (definterface pathname-to-filename (pathname)
    578   "Return the filename for PATHNAME."
    579   (namestring pathname))
    580 
    581 (definterface default-directory ()
    582   "Return the default directory."
    583   (directory-namestring (truename *default-pathname-defaults*)))
    584 
    585 (definterface set-default-directory (directory)
    586   "Set the default directory.
    587 This is used to resolve filenames without directory component."
    588   (setf *default-pathname-defaults* (truename (merge-pathnames directory)))
    589   (default-directory))
    590 
    591 
    592 (definterface call-with-syntax-hooks (fn)
    593   "Call FN with hooks to handle special syntax."
    594   (funcall fn))
    595 
    596 (definterface default-readtable-alist ()
    597   "Return a suitable initial value for SLYNK:*READTABLE-ALIST*."
    598   '())
    599 
    600 
    601 ;;;; Packages
    602 
    603 (definterface package-local-nicknames (package)
    604   "Returns an alist of (local-nickname . actual-package) describing the
    605 nicknames local to the designated package."
    606   (declare (ignore package))
    607   nil)
    608 
    609 (definterface find-locally-nicknamed-package (name base-package)
    610   "Return the package whose local nickname in BASE-PACKAGE matches NAME.
    611 Return NIL if local nicknames are not implemented or if there is no
    612 such package."
    613   (cdr (assoc name (package-local-nicknames base-package) :test #'string-equal)))
    614 
    615 
    616 ;;;; Compilation
    617 
    618 (definterface call-with-compilation-hooks (func)
    619   "Call FUNC with hooks to record compiler conditions.")
    620 
    621 (defmacro with-compilation-hooks ((&rest ignore) &body body)
    622   "Execute BODY as in CALL-WITH-COMPILATION-HOOKS."
    623   (declare (ignore ignore))
    624   `(call-with-compilation-hooks (lambda () (progn ,@body))))
    625 
    626 (definterface slynk-compile-string (string &key buffer position filename
    627                                            line column policy)
    628   "Compile source from STRING.
    629 During compilation, compiler conditions must be trapped and
    630 resignalled as COMPILER-CONDITIONs.
    631 
    632 If supplied, BUFFER and POSITION specify the source location in Emacs.
    633 
    634 Additionally, if POSITION is supplied, it must be added to source
    635 positions reported in compiler conditions.
    636 
    637 If FILENAME is specified it may be used by certain implementations to
    638 rebind *DEFAULT-PATHNAME-DEFAULTS* which may improve the recording of
    639 source information.
    640 
    641 If POLICY is supplied, and non-NIL, it may be used by certain
    642 implementations to compile with optimization qualities of its
    643 value.
    644 
    645 If LINE and COLUMN are supplied, and non-NIL, they may be used by
    646 certain implementations (presumably instead of POSITION) as the line
    647 and column of the start of the string in FILENAME. Both LINE and
    648 COLUMN are 1-based.
    649 
    650 Should return T on successful compilation, NIL otherwise.
    651 ")
    652 
    653 (definterface slynk-compile-file (input-file output-file load-p
    654                                              external-format
    655                                              &key policy)
    656    "Compile INPUT-FILE signalling COMPILE-CONDITIONs.
    657 If LOAD-P is true, load the file after compilation.
    658 EXTERNAL-FORMAT is a value returned by find-external-format or
    659 :default.
    660 
    661 If POLICY is supplied, and non-NIL, it may be used by certain
    662 implementations to compile with optimization qualities of its
    663 value.
    664 
    665 Should return OUTPUT-TRUENAME, WARNINGS-P and FAILURE-p
    666 like `compile-file'")
    667 
    668 (deftype severity ()
    669   '(member :error :read-error :warning :style-warning :note :redefinition))
    670 
    671 ;; Base condition type for compiler errors, warnings and notes.
    672 (define-condition compiler-condition (condition)
    673   ((original-condition
    674     ;; The original condition thrown by the compiler if appropriate.
    675     ;; May be NIL if a compiler does not report using conditions.
    676     :type (or null condition)
    677     :initarg :original-condition
    678     :accessor original-condition)
    679 
    680    (severity :type severity
    681              :initarg :severity
    682              :accessor severity)
    683 
    684    (message :initarg :message
    685             :accessor message)
    686 
    687    ;; Macro expansion history etc. which may be helpful in some cases
    688    ;; but is often very verbose.
    689    (source-context :initarg :source-context
    690                    :type (or null string)
    691                    :initform nil
    692                    :accessor source-context)
    693 
    694    (references :initarg :references
    695                :initform nil
    696                :accessor references)
    697 
    698    (location :initarg :location
    699              :accessor location)))
    700 
    701 (definterface find-external-format (coding-system)
    702   "Return a \"external file format designator\" for CODING-SYSTEM.
    703 CODING-SYSTEM is Emacs-style coding system name (a string),
    704 e.g. \"latin-1-unix\"."
    705   (if (equal coding-system "iso-latin-1-unix")
    706       :default
    707       nil))
    708 
    709 (definterface guess-external-format (pathname)
    710   "Detect the external format for the file with name pathname.
    711 Return nil if the file contains no special markers."
    712   ;; Look for a Emacs-style -*- coding: ... -*- or Local Variable: section.
    713   (with-open-file (s pathname :if-does-not-exist nil
    714                      :external-format (or (find-external-format "latin-1-unix")
    715                                           :default))
    716     (if s
    717         (or (let* ((line (read-line s nil))
    718                    (p (search "-*-" line)))
    719               (when p
    720                 (let* ((start (+ p (length "-*-")))
    721                        (end (search "-*-" line :start2 start)))
    722                   (when end
    723                     (%search-coding line start end)))))
    724             (let* ((len (file-length s))
    725                    (buf (make-string (min len 3000))))
    726               (file-position s (- len (length buf)))
    727               (read-sequence buf s)
    728               (let ((start (search "Local Variables:" buf :from-end t))
    729                     (end (search "End:" buf :from-end t)))
    730                 (and start end (< start end)
    731                      (%search-coding buf start end))))))))
    732 
    733 (defun %search-coding (str start end)
    734   (let ((p (search "coding:" str :start2 start :end2 end)))
    735     (when p
    736       (incf p (length "coding:"))
    737       (loop while (and (< p end)
    738                        (member (aref str p) '(#\space #\tab)))
    739             do (incf p))
    740       (let ((end (position-if (lambda (c) (find c '(#\space #\tab #\newline #\;)))
    741                               str :start p)))
    742         (find-external-format (subseq str p end))))))
    743 
    744 
    745 ;;;; Streams
    746 
    747 (definterface make-output-stream (write-string)
    748   "Return a new character output stream.
    749 The stream calls WRITE-STRING when output is ready.")
    750 
    751 (definterface make-input-stream (read-string)
    752   "Return a new character input stream.
    753 The stream calls READ-STRING when input is needed.")
    754 
    755 (defvar *auto-flush-interval* 0.2)
    756 
    757 (defun auto-flush-loop (stream interval &optional receive)
    758   (loop
    759     (when (not (and (open-stream-p stream)
    760                     (output-stream-p stream)))
    761       (return nil))
    762     (force-output stream)
    763     (when receive
    764       (receive-if #'identity))
    765     (sleep interval)))
    766 
    767 (definterface make-auto-flush-thread (stream)
    768   "Make an auto-flush thread"
    769   (spawn (lambda () (auto-flush-loop stream *auto-flush-interval* nil))
    770          :name "auto-flush-thread"))
    771 
    772 
    773 ;;;; Documentation
    774 
    775 (definterface arglist (name)
    776    "Return the lambda list for the symbol NAME. NAME can also be
    777 a lisp function object, on lisps which support this.
    778 
    779 The result can be a list or the :not-available keyword if the
    780 arglist cannot be determined."
    781    (declare (ignore name))
    782    :not-available)
    783 
    784 (defgeneric declaration-arglist (decl-identifier)
    785   (:documentation
    786    "Return the argument list of the declaration specifier belonging to the
    787 declaration identifier DECL-IDENTIFIER. If the arglist cannot be determined,
    788 the keyword :NOT-AVAILABLE is returned.
    789 
    790 The different SLYNK backends can specialize this generic function to
    791 include implementation-dependend declaration specifiers, or to provide
    792 additional information on the specifiers defined in ANSI Common Lisp.")
    793   (:method (decl-identifier)
    794     (case decl-identifier
    795       (dynamic-extent '(&rest variables))
    796       (ignore         '(&rest variables))
    797       (ignorable      '(&rest variables))
    798       (special        '(&rest variables))
    799       (inline         '(&rest function-names))
    800       (notinline      '(&rest function-names))
    801       (declaration    '(&rest names))
    802       (optimize       '(&any compilation-speed debug safety space speed))
    803       (type           '(type-specifier &rest args))
    804       (ftype          '(type-specifier &rest function-names))
    805       (otherwise
    806        (flet ((typespec-p (symbol)
    807                 (member :type (describe-symbol-for-emacs symbol))))
    808          (cond ((and (symbolp decl-identifier) (typespec-p decl-identifier))
    809                 '(&rest variables))
    810                ((and (listp decl-identifier)
    811                      (typespec-p (first decl-identifier)))
    812                 '(&rest variables))
    813                (t :not-available)))))))
    814 
    815 (defgeneric type-specifier-arglist (typespec-operator)
    816   (:documentation
    817    "Return the argument list of the type specifier belonging to
    818 TYPESPEC-OPERATOR.. If the arglist cannot be determined, the keyword
    819 :NOT-AVAILABLE is returned.
    820 
    821 The different SLYNK backends can specialize this generic function to
    822 include implementation-dependend declaration specifiers, or to provide
    823 additional information on the specifiers defined in ANSI Common Lisp.")
    824   (:method (typespec-operator)
    825     (declare (special *type-specifier-arglists*)) ; defined at end of file.
    826     (typecase typespec-operator
    827       (symbol (or (cdr (assoc typespec-operator *type-specifier-arglists*))
    828                   :not-available))
    829       (t :not-available))))
    830 
    831 (definterface type-specifier-p (symbol)
    832   "Determine if SYMBOL is a type-specifier."
    833   (or (documentation symbol 'type)
    834       (not (eq (type-specifier-arglist symbol) :not-available))))
    835 
    836 (definterface function-name (function)
    837   "Return the name of the function object FUNCTION.
    838 
    839 The result is either a symbol, a list, or NIL if no function name is
    840 available."
    841   (declare (ignore function))
    842   nil)
    843 
    844 (definterface valid-function-name-p (form)
    845   "Is FORM syntactically valid to name a function?
    846    If true, FBOUNDP should not signal a type-error for FORM."
    847   (flet ((length=2 (list)
    848            (and (not (null (cdr list))) (null (cddr list)))))
    849     (or (symbolp form)
    850         (and (consp form) (length=2 form)
    851              (eq (first form) 'setf) (symbolp (second form))))))
    852 
    853 (definterface macroexpand-all (form &optional env)
    854    "Recursively expand all macros in FORM.
    855 Return the resulting form.")
    856 
    857 (definterface compiler-macroexpand-1 (form &optional env)
    858   "Call the compiler-macro for form.
    859 If FORM is a function call for which a compiler-macro has been
    860 defined, invoke the expander function using *macroexpand-hook* and
    861 return the results and T.  Otherwise, return the original form and
    862 NIL."
    863   (let ((fun (and (consp form)
    864                   (valid-function-name-p (car form))
    865                   (compiler-macro-function (car form) env))))
    866     (if fun
    867 	(let ((result (funcall *macroexpand-hook* fun form env)))
    868           (values result (not (eq result form))))
    869 	(values form nil))))
    870 
    871 (definterface compiler-macroexpand (form &optional env)
    872   "Repetitively call `compiler-macroexpand-1'."
    873   (labels ((frob (form expanded)
    874              (multiple-value-bind (new-form newly-expanded)
    875                  (compiler-macroexpand-1 form env)
    876                (if newly-expanded
    877                    (frob new-form t)
    878                    (values new-form expanded)))))
    879     (frob form env)))
    880 
    881 (definterface format-string-expand (control-string)
    882   "Expand the format string CONTROL-STRING."
    883   (macroexpand `(formatter ,control-string)))
    884 
    885 (definterface describe-symbol-for-emacs (symbol)
    886    "Return a property list describing SYMBOL.
    887 
    888 The property list has an entry for each interesting aspect of the
    889 symbol. The recognised keys are:
    890 
    891   :VARIABLE :FUNCTION :SETF :SPECIAL-OPERATOR :MACRO :COMPILER-MACRO
    892   :TYPE :CLASS :ALIEN-TYPE :ALIEN-STRUCT :ALIEN-UNION :ALIEN-ENUM
    893 
    894 The value of each property is the corresponding documentation string,
    895 or NIL (or the obsolete :NOT-DOCUMENTED). It is legal to include keys
    896 not listed here (but sly-print-apropos in Emacs must know about
    897 them).
    898 
    899 Properties should be included if and only if they are applicable to
    900 the symbol. For example, only (and all) fbound symbols should include
    901 the :FUNCTION property.
    902 
    903 Example:
    904 \(describe-symbol-for-emacs 'vector)
    905   => (:CLASS :NOT-DOCUMENTED
    906       :TYPE :NOT-DOCUMENTED
    907       :FUNCTION \"Constructs a simple-vector from the given objects.\")")
    908 
    909 (definterface describe-definition (name type)
    910   "Describe the definition NAME of TYPE.
    911 TYPE can be any value returned by DESCRIBE-SYMBOL-FOR-EMACS.
    912 
    913 Return a documentation string, or NIL if none is available.")
    914 
    915 (definterface make-apropos-matcher (pattern symbol-name-fn
    916                                             &optional
    917                                             case-sensitive)
    918   "Produce unary function that looks for PATTERN in symbol names.
    919 SYMBOL-NAME-FN must be applied to symbol-names to produce the string
    920 where PATTERN should be searched for.  CASE-SENSITIVE indicates
    921 case-sensitivity. On a positive match, the function returned must
    922 return non-nil values, which may be pairs of indexes to highlight in
    923 the symbol designation's string.")
    924 
    925 
    926 
    927 ;;;; Debugging
    928 
    929 (definterface install-debugger-globally (function)
    930   "Install FUNCTION as the debugger for all threads/processes. This
    931 usually involves setting *DEBUGGER-HOOK* and, if the implementation
    932 permits, hooking into BREAK as well."
    933   (setq *debugger-hook* function))
    934 
    935 (definterface call-with-debugging-environment (debugger-loop-fn)
    936    "Call DEBUGGER-LOOP-FN in a suitable debugging environment.
    937 
    938 This function is called recursively at each debug level to invoke the
    939 debugger loop. The purpose is to setup any necessary environment for
    940 other debugger callbacks that will be called within the debugger loop.
    941 
    942 For example, this is a reasonable place to compute a backtrace, switch
    943 to safe reader/printer settings, and so on.")
    944 
    945 (definterface call-with-debugger-hook (hook fun)
    946   "Call FUN and use HOOK as debugger hook. HOOK can be NIL.
    947 
    948 HOOK should be called for both BREAK and INVOKE-DEBUGGER."
    949   (let ((*debugger-hook* hook))
    950     (funcall fun)))
    951 
    952 (define-condition sly-db-condition (condition)
    953   ((original-condition
    954     :initarg :original-condition
    955     :accessor original-condition))
    956   (:report (lambda (condition stream)
    957              (format stream "Condition in debugger code~@[: ~A~]"
    958                      (original-condition condition))))
    959   (:documentation
    960    "Wrapper for conditions that should not be debugged.
    961 
    962 When a condition arises from the internals of the debugger, it is not
    963 desirable to debug it -- we'd risk entering an endless loop trying to
    964 debug the debugger! Instead, such conditions can be reported to the
    965 user without (re)entering the debugger by wrapping them as
    966 `sly-db-condition's."))
    967 
    968 ;;; The following functions in this section are supposed to be called
    969 ;;; within the dynamic contour of CALL-WITH-DEBUGGING-ENVIRONMENT only.
    970 
    971 (definterface compute-backtrace (start end)
    972    "Returns a backtrace of the condition currently being debugged,
    973 that is an ordered list consisting of frames. ``Ordered list''
    974 means that an integer I can be mapped back to the i-th frame of this
    975 backtrace.
    976 
    977 START and END are zero-based indices constraining the number of frames
    978 returned. Frame zero is defined as the frame which invoked the
    979 debugger. If END is nil, return the frames from START to the end of
    980 the stack.")
    981 
    982 (definterface print-frame (frame stream)
    983   "Print frame to stream.")
    984 
    985 (definterface frame-restartable-p (frame)
    986   "Is the frame FRAME restartable?.
    987 Return T if `restart-frame' can safely be called on the frame."
    988   (declare (ignore frame))
    989   nil)
    990 
    991 (definterface frame-source-location (frame-number)
    992   "Return the source location for the frame associated to FRAME-NUMBER.")
    993 
    994 (definterface frame-catch-tags (frame-number)
    995   "Return a list of catch tags for being printed in a debugger stack
    996 frame."
    997   (declare (ignore frame-number))
    998   '())
    999 
   1000 (definterface frame-locals (frame-number)
   1001   "Return a list of ((&key NAME ID VALUE) ...) where each element of
   1002 the list represents a local variable in the stack frame associated to
   1003 FRAME-NUMBER.
   1004 
   1005 NAME, a symbol; the name of the local variable.
   1006 
   1007 ID, an integer; used as primary key for the local variable, unique
   1008 relatively to the frame under operation.
   1009 
   1010 value, an object; the value of the local variable.")
   1011 
   1012 (definterface frame-var-value (frame-number var-id)
   1013   "Return the value of the local variable associated to VAR-ID
   1014 relatively to the frame associated to FRAME-NUMBER.")
   1015 
   1016 (definterface disassemble-frame (frame-number)
   1017   "Disassemble the code for the FRAME-NUMBER.
   1018 The output should be written to standard output.
   1019 FRAME-NUMBER is a non-negative integer.")
   1020 
   1021 (definterface eval-in-frame (form frame-number)
   1022    "Evaluate a Lisp form in the lexical context of a stack frame
   1023 in the debugger.
   1024 
   1025 FRAME-NUMBER must be a positive integer with 0 indicating the
   1026 frame which invoked the debugger.
   1027 
   1028 The return value is the result of evaulating FORM in the
   1029 appropriate context.")
   1030 
   1031 (definterface frame-package (frame-number)
   1032   "Return the package corresponding to the frame at FRAME-NUMBER.
   1033 Return nil if the backend can't figure it out."
   1034   (declare (ignore frame-number))
   1035   nil)
   1036 
   1037 (definterface frame-arguments (frame-number)
   1038   "Return the arguments passed to frame at FRAME-NUMBER as a values list.
   1039 Default values of optional arguments not passed in by the user may or
   1040 may not be returned.")
   1041 
   1042 (definterface return-from-frame (frame-number form)
   1043   "Unwind the stack to the frame FRAME-NUMBER and return the value(s)
   1044 produced by evaluating FORM in the frame context to its caller.
   1045 
   1046 Execute any clean-up code from unwind-protect forms above the frame
   1047 during unwinding.
   1048 
   1049 Return a string describing the error if it's not possible to return
   1050 from the frame.")
   1051 
   1052 (definterface restart-frame (frame-number)
   1053   "Restart execution of the frame FRAME-NUMBER with the same arguments
   1054 as it was called originally.")
   1055 
   1056 (definterface print-condition (condition stream)
   1057   "Print a condition for display in SLY-DB."
   1058   (princ condition stream))
   1059 
   1060 (definterface condition-extras (condition)
   1061   "Return a list of extra for the debugger.
   1062 The allowed elements are of the form:
   1063   (:SHOW-FRAME-SOURCE frame-number)
   1064   (:REFERENCES &rest refs)
   1065 "
   1066   (declare (ignore condition))
   1067   '())
   1068 
   1069 (definterface gdb-initial-commands ()
   1070   "List of gdb commands supposed to be executed first for the
   1071    ATTACH-GDB restart."
   1072   nil)
   1073 
   1074 (definterface activate-stepping (frame-number)
   1075   "Prepare the frame FRAME-NUMBER for stepping.")
   1076 
   1077 (definterface sly-db-break-on-return (frame-number)
   1078   "Set a breakpoint in the frame FRAME-NUMBER.")
   1079 
   1080 (definterface sly-db-break-at-start (symbol)
   1081   "Set a breakpoint on the beginning of the function for SYMBOL.")
   1082 
   1083 (definterface sly-db-stepper-condition-p (condition)
   1084   "Return true if SLY-DB was invoked due to a single-stepping condition,
   1085 false otherwise. "
   1086   (declare (ignore condition))
   1087   nil)
   1088 
   1089 (definterface sly-db-step-into ()
   1090   "Step into the current single-stepper form.")
   1091 
   1092 (definterface sly-db-step-next ()
   1093   "Step to the next form in the current function.")
   1094 
   1095 (definterface sly-db-step-out ()
   1096   "Stop single-stepping temporarily, but resume it once the current function
   1097 returns.")
   1098 
   1099 
   1100 ;;;; Definition finding
   1101 
   1102 (defstruct (location (:type list)
   1103                       (:constructor make-location
   1104                           (buffer position &optional hints)))
   1105   (type :location)
   1106   buffer position
   1107   ;; Hints is a property list optionally containing:
   1108   ;;   :snippet SOURCE-TEXT
   1109   ;;     This is a snippet of the actual source text at the start of
   1110   ;;     the definition, which could be used in a text search.
   1111   hints)
   1112 
   1113 (defmacro converting-errors-to-error-location (&body body)
   1114   "Catches errors during BODY and converts them to an error location."
   1115   (let ((gblock (gensym "CONVERTING-ERRORS+")))
   1116     `(block ,gblock
   1117        (handler-bind ((error
   1118                        #'(lambda (e)
   1119                             (if *debug-slynk-backend*
   1120                                 nil     ;decline
   1121                                 (return-from ,gblock
   1122                                   (make-error-location e))))))
   1123          ,@body))))
   1124 
   1125 (defun make-error-location (datum &rest args)
   1126   (cond ((typep datum 'condition)
   1127          `(:error ,(format nil "Error: ~A" datum)))
   1128         ((symbolp datum)
   1129          `(:error ,(format nil "Error: ~A"
   1130                            (apply #'make-condition datum args))))
   1131         (t
   1132          (assert (stringp datum))
   1133          `(:error ,(apply #'format nil datum args)))))
   1134 
   1135 (definterface find-definitions (name)
   1136    "Return a list ((DSPEC LOCATION) ...) for NAME's definitions.
   1137 
   1138 NAME is a \"definition specifier\".
   1139 
   1140 DSPEC is a \"definition specifier\" describing the
   1141 definition, e.g., FOO or (METHOD FOO (STRING NUMBER)) or
   1142 \(DEFVAR FOO).
   1143 
   1144 LOCATION is the source location for the definition.")
   1145 
   1146 (definterface find-source-location (object)
   1147   "Returns the source location of OBJECT, or NIL.
   1148 
   1149 That is the source location of the underlying datastructure of
   1150 OBJECT. E.g. on a STANDARD-OBJECT, the source location of the
   1151 respective DEFCLASS definition is returned, on a STRUCTURE-CLASS the
   1152 respective DEFSTRUCT definition, and so on."
   1153   ;; This returns one source location and not a list of locations. It's
   1154   ;; supposed to return the location of the DEFGENERIC definition on
   1155   ;; #'SOME-GENERIC-FUNCTION.
   1156   (declare (ignore object))
   1157   (make-error-location "FIND-SOURCE-LOCATION is not yet implemented on ~
   1158                         this implementation."))
   1159 
   1160 (definterface buffer-first-change (filename)
   1161   "Called for effect the first time FILENAME's buffer is modified.
   1162 CMUCL/SBCL use this to cache the unmodified file and use the
   1163 unmodified text to improve the precision of source locations."
   1164   (declare (ignore filename))
   1165   nil)
   1166 
   1167 
   1168 
   1169 ;;;; XREF
   1170 
   1171 (definterface who-calls (function-name)
   1172   "Return the call sites of FUNCTION-NAME (a symbol).
   1173 The results is a list ((DSPEC LOCATION) ...)."
   1174   (declare (ignore function-name))
   1175   :not-implemented)
   1176 
   1177 (definterface calls-who (function-name)
   1178   "Return the list of functions called by FUNCTION-NAME (a symbol).
   1179 The results is a list ((DSPEC LOCATION) ...)."
   1180   (declare (ignore function-name))
   1181   :not-implemented)
   1182 
   1183 (definterface who-references (variable-name)
   1184   "Return the locations where VARIABLE-NAME (a symbol) is referenced.
   1185 See WHO-CALLS for a description of the return value."
   1186   (declare (ignore variable-name))
   1187   :not-implemented)
   1188 
   1189 (definterface who-binds (variable-name)
   1190   "Return the locations where VARIABLE-NAME (a symbol) is bound.
   1191 See WHO-CALLS for a description of the return value."
   1192   (declare (ignore variable-name))
   1193   :not-implemented)
   1194 
   1195 (definterface who-sets (variable-name)
   1196   "Return the locations where VARIABLE-NAME (a symbol) is set.
   1197 See WHO-CALLS for a description of the return value."
   1198   (declare (ignore variable-name))
   1199   :not-implemented)
   1200 
   1201 (definterface who-macroexpands (macro-name)
   1202   "Return the locations where MACRO-NAME (a symbol) is expanded.
   1203 See WHO-CALLS for a description of the return value."
   1204   (declare (ignore macro-name))
   1205   :not-implemented)
   1206 
   1207 (definterface who-specializes (class-name)
   1208   "Return the locations where CLASS-NAME (a symbol) is specialized.
   1209 See WHO-CALLS for a description of the return value."
   1210   (declare (ignore class-name))
   1211   :not-implemented)
   1212 
   1213 ;;; Simpler variants.
   1214 
   1215 (definterface list-callers (function-name)
   1216   "List the callers of FUNCTION-NAME.
   1217 This function is like WHO-CALLS except that it is expected to use
   1218 lower-level means. Whereas WHO-CALLS is usually implemented with
   1219 special compiler support, LIST-CALLERS is usually implemented by
   1220 groveling for constants in function objects throughout the heap.
   1221 
   1222 The return value is as for WHO-CALLS.")
   1223 
   1224 (definterface list-callees (function-name)
   1225   "List the functions called by FUNCTION-NAME.
   1226 See LIST-CALLERS for a description of the return value.")
   1227 
   1228 
   1229 ;;;; Profiling
   1230 
   1231 ;;; The following functions define a minimal profiling interface.
   1232 
   1233 (definterface profile (fname)
   1234   "Marks symbol FNAME for profiling.")
   1235 
   1236 (definterface profiled-functions ()
   1237   "Returns a list of profiled functions.")
   1238 
   1239 (definterface unprofile (fname)
   1240   "Marks symbol FNAME as not profiled.")
   1241 
   1242 (definterface unprofile-all ()
   1243   "Marks all currently profiled functions as not profiled."
   1244   (dolist (f (profiled-functions))
   1245     (unprofile f)))
   1246 
   1247 (definterface profile-report ()
   1248   "Prints profile report.")
   1249 
   1250 (definterface profile-reset ()
   1251   "Resets profile counters.")
   1252 
   1253 (definterface profile-package (package callers-p methods)
   1254   "Wrap profiling code around all functions in PACKAGE.  If a function
   1255 is already profiled, then unprofile and reprofile (useful to notice
   1256 function redefinition.)
   1257 
   1258 If CALLERS-P is T names have counts of the most common calling
   1259 functions recorded.
   1260 
   1261 When called with arguments :METHODS T, profile all methods of all
   1262 generic functions having names in the given package.  Generic functions
   1263 themselves, that is, their dispatch functions, are left alone.")
   1264 
   1265 
   1266 ;;;; Trace
   1267 
   1268 (definterface toggle-trace (spec)
   1269   "Toggle tracing of the function(s) given with SPEC.
   1270 SPEC can be:
   1271  (setf NAME)                            ; a setf function
   1272  (:defmethod NAME QUALIFIER... (SPECIALIZER...)) ; a specific method
   1273  (:defgeneric NAME)                     ; a generic function with all methods
   1274  (:call CALLER CALLEE)                  ; trace calls from CALLER to CALLEE.
   1275  (:labels TOPLEVEL LOCAL)
   1276  (:flet TOPLEVEL LOCAL) ")
   1277 
   1278 
   1279 ;;;; Inspector
   1280 
   1281 (defgeneric emacs-inspect (object)
   1282   (:documentation
   1283    "Explain to Emacs how to inspect OBJECT.
   1284 
   1285 Returns a list specifying how to render the object for inspection.
   1286 
   1287 Every element of the list must be either a string, which will be
   1288 inserted into the buffer as is, or a list of the form:
   1289 
   1290  (:value object &optional format) - Render an inspectable
   1291  object. If format is provided it must be a string and will be
   1292  rendered in place of the value, otherwise use princ-to-string.
   1293 
   1294  (:newline) - Render a \\n
   1295 
   1296  (:action label lambda &key (refresh t)) - Render LABEL (a text
   1297  string) which when clicked will call LAMBDA. If REFRESH is
   1298  non-NIL the currently inspected object will be re-inspected
   1299  after calling the lambda.
   1300 "))
   1301 
   1302 (defmethod emacs-inspect ((object t))
   1303   "Generic method for inspecting any kind of object.
   1304 
   1305 Since we don't know how to deal with OBJECT we simply dump the
   1306 output of CL:DESCRIBE."
   1307    `("Type: " (:value ,(type-of object)) (:newline)
   1308      "Don't know how to inspect the object, dumping output of CL:DESCRIBE:"
   1309      (:newline) (:newline)
   1310      ,(with-output-to-string (desc) (describe object desc))))
   1311 
   1312 (definterface eval-context (object)
   1313   "Return a list of bindings corresponding to OBJECT's slots."
   1314   (declare (ignore object))
   1315   '())
   1316 
   1317 ;;; Utilities for inspector methods.
   1318 ;;;
   1319 
   1320 (defun label-value-line (label value &key (newline t))
   1321   "Create a control list which prints \"LABEL: VALUE\" in the inspector.
   1322 If NEWLINE is non-NIL a `(:newline)' is added to the result."
   1323   (list* (princ-to-string label) ": " `(:value ,value)
   1324          (if newline '((:newline)) nil)))
   1325 
   1326 (defmacro label-value-line* (&rest label-values)
   1327   ` (append ,@(loop for (label value) in label-values
   1328                     collect `(label-value-line ,label ,value))))
   1329 
   1330 (definterface describe-primitive-type (object)
   1331   "Return a string describing the primitive type of object."
   1332   (declare (ignore object))
   1333   "N/A")
   1334 
   1335 
   1336 ;;;; Multithreading
   1337 ;;;
   1338 ;;; The default implementations are sufficient for non-multiprocessing
   1339 ;;; implementations.
   1340 
   1341 (definterface initialize-multiprocessing (continuation)
   1342    "Initialize multiprocessing, if necessary and then invoke CONTINUATION.
   1343 
   1344 Depending on the impleimentaion, this function may never return."
   1345    (funcall continuation))
   1346 
   1347 (definterface spawn (fn &key name)
   1348   "Create a new thread to call FN.")
   1349 
   1350 (definterface thread-id (thread)
   1351   "Return an Emacs-parsable object to identify THREAD.
   1352 
   1353 Ids should be comparable with equal, i.e.:
   1354  (equal (thread-id <t1>) (thread-id <t2>)) <==> (eq <t1> <t2>)"
   1355   thread)
   1356 
   1357 (definterface find-thread (id)
   1358   "Return the thread for ID.
   1359 ID should be an id previously obtained with THREAD-ID.
   1360 Can return nil if the thread no longer exists."
   1361   (declare (ignore id))
   1362   (current-thread))
   1363 
   1364 (definterface thread-name (thread)
   1365    "Return the name of THREAD.
   1366 Thread names are short strings meaningful to the user. They do not
   1367 have to be unique."
   1368    (declare (ignore thread))
   1369    "The One True Thread")
   1370 
   1371 (definterface thread-status (thread)
   1372    "Return a string describing THREAD's state."
   1373    (declare (ignore thread))
   1374    "")
   1375 
   1376 (definterface thread-attributes (thread)
   1377   "Return a plist of implementation-dependent attributes for THREAD"
   1378   (declare (ignore thread))
   1379   '())
   1380 
   1381 (definterface current-thread ()
   1382   "Return the currently executing thread."
   1383   0)
   1384 
   1385 (definterface all-threads ()
   1386   "Return a fresh list of all threads."
   1387   '())
   1388 
   1389 (definterface thread-alive-p (thread)
   1390   "Test if THREAD is termintated."
   1391   (member thread (all-threads)))
   1392 
   1393 (definterface interrupt-thread (thread fn)
   1394   "Cause THREAD to execute FN.")
   1395 
   1396 (definterface kill-thread (thread)
   1397   "Terminate THREAD immediately.
   1398 Don't execute unwind-protected sections, don't raise conditions.
   1399 (Do not pass go, do not collect $200.)"
   1400   (declare (ignore thread))
   1401   nil)
   1402 
   1403 (definterface send (thread object)
   1404   "Send OBJECT to thread THREAD."
   1405   (declare (ignore thread))
   1406   object)
   1407 
   1408 (definterface receive (&optional timeout)
   1409   "Return the next message from current thread's mailbox."
   1410   (receive-if (constantly t) timeout))
   1411 
   1412 (definterface receive-if (predicate &optional timeout)
   1413   "Return the first message satisfiying PREDICATE.")
   1414 
   1415 (definterface wake-thread (thread)
   1416   "Trigger a call to CHECK-SLIME-INTERRUPTS in THREAD without using
   1417 asynchronous interrupts."
   1418   (declare (ignore thread))
   1419   ;; Doesn't have to implement this if RECEIVE-IF periodically calls
   1420   ;; CHECK-SLIME-INTERRUPTS, but that's energy inefficient
   1421   nil)
   1422 
   1423 (definterface register-thread (name thread)
   1424   "Associate the thread THREAD with the symbol NAME.
   1425 The thread can then be retrieved with `find-registered'.
   1426 If THREAD is nil delete the association."
   1427   (declare (ignore name thread))
   1428   nil)
   1429 
   1430 (definterface find-registered (name)
   1431   "Find the thread that was registered for the symbol NAME.
   1432 Return nil if the no thread was registred or if the tread is dead."
   1433   (declare (ignore name))
   1434   nil)
   1435 
   1436 (definterface set-default-initial-binding (var form)
   1437   "Initialize special variable VAR by default with FORM.
   1438 
   1439 Some implementations initialize certain variables in each newly
   1440 created thread.  This function sets the form which is used to produce
   1441 the initial value."
   1442   (set var (eval form)))
   1443 
   1444 ;; List of delayed interrupts.
   1445 ;; This should only have thread-local bindings, so no init form.
   1446 (defvar *pending-sly-interrupts*)
   1447 
   1448 (defun check-sly-interrupts ()
   1449   "Execute pending interrupts if any.
   1450 This should be called periodically in operations which
   1451 can take a long time to complete.
   1452 Return a boolean indicating whether any interrupts was processed."
   1453   (when (and (boundp '*pending-sly-interrupts*)
   1454              *pending-sly-interrupts*)
   1455     (funcall (pop *pending-sly-interrupts*))
   1456     t))
   1457 
   1458 (defvar *interrupt-queued-handler* nil
   1459   "Function to call on queued interrupts.
   1460 Interrupts get queued when an interrupt occurs while interrupt
   1461 handling is disabled.
   1462 
   1463 Backends can use this function to abort slow operations.")
   1464 
   1465 (definterface wait-for-input (streams &optional timeout)
   1466   "Wait for input on a list of streams.  Return those that are ready.
   1467 STREAMS is a list of streams
   1468 TIMEOUT nil, t, or real number. If TIMEOUT is t, return those streams
   1469 which are ready (or have reached end-of-file) without waiting.
   1470 If TIMEOUT is a number and no streams is ready after TIMEOUT seconds,
   1471 return nil.
   1472 
   1473 Return :interrupt if an interrupt occurs while waiting."
   1474   (declare (ignore streams timeout))
   1475   ;; Invoking the slime debugger will just endlessly loop.
   1476   (call-with-debugger-hook
   1477    nil
   1478    (lambda ()
   1479      (error
   1480       "~s not implemented. Check if ~s = ~s is supported by the implementation."
   1481       'wait-for-input
   1482       (read-from-string "SLYNK:*COMMUNICATION-STYLE*")
   1483       (symbol-value (read-from-string "SLYNK:*COMMUNICATION-STYLE*"))))))
   1484 
   1485 
   1486 ;;;;  Locks
   1487 
   1488 ;; Please use locks only in slynk-gray.lisp.  Locks are too low-level
   1489 ;; for our taste.
   1490 
   1491 (definterface make-lock (&key name)
   1492    "Make a lock for thread synchronization.
   1493 Only one thread may hold the lock (via CALL-WITH-LOCK-HELD) at a time
   1494 but that thread may hold it more than once."
   1495    (declare (ignore name))
   1496    :null-lock)
   1497 
   1498 (definterface call-with-lock-held (lock function)
   1499    "Call FUNCTION with LOCK held, queueing if necessary."
   1500    (declare (ignore lock)
   1501             (type function function))
   1502    (funcall function))
   1503 
   1504 
   1505 ;;;; Weak datastructures
   1506 
   1507 (definterface make-weak-key-hash-table (&rest args)
   1508   "Like MAKE-HASH-TABLE, but weak w.r.t. the keys."
   1509   (apply #'make-hash-table args))
   1510 
   1511 (definterface make-weak-value-hash-table (&rest args)
   1512   "Like MAKE-HASH-TABLE, but weak w.r.t. the values."
   1513   (apply #'make-hash-table args))
   1514 
   1515 (definterface hash-table-weakness (hashtable)
   1516   "Return nil or one of :key :value :key-or-value :key-and-value"
   1517   (declare (ignore hashtable))
   1518   nil)
   1519 
   1520 
   1521 ;;;; Floating point
   1522 
   1523 (definterface float-nan-p (float)
   1524   "Return true if FLOAT is a NaN value (Not a Number)."
   1525   ;; When the float type implements IEEE-754 floats, two NaN values
   1526   ;; are never equal; when the implementation does not support NaN,
   1527   ;; the predicate should return false. An implementation can
   1528   ;; implement comparison with "unordered-signaling predicates", which
   1529   ;; emit floating point exceptions.
   1530   (handler-case (not (= float float))
   1531     ;; Comparisons never signal an exception other than the invalid
   1532     ;; operation exception (5.11 Details of comparison predicates).
   1533     (floating-point-invalid-operation () t)))
   1534 
   1535 (definterface float-infinity-p (float)
   1536   "Return true if FLOAT is positive or negative infinity."
   1537   (not (< most-negative-long-float
   1538           float
   1539           most-positive-long-float)))
   1540 
   1541 
   1542 ;;;; Character names
   1543 
   1544 (definterface character-completion-set (prefix matchp)
   1545   "Return a list of names of characters that match PREFIX."
   1546   ;; Handle the standard and semi-standard characters.
   1547   (loop for name in '("Newline" "Space" "Tab" "Page" "Rubout"
   1548                       "Linefeed" "Return" "Backspace")
   1549      when (funcall matchp prefix name)
   1550      collect name))
   1551 
   1552 
   1553 (defparameter *type-specifier-arglists*
   1554   '((and                . (&rest type-specifiers))
   1555     (array              . (&optional element-type dimension-spec))
   1556     (base-string        . (&optional size))
   1557     (bit-vector         . (&optional size))
   1558     (complex            . (&optional type-specifier))
   1559     (cons               . (&optional car-typespec cdr-typespec))
   1560     (double-float       . (&optional lower-limit upper-limit))
   1561     (eql                . (object))
   1562     (float              . (&optional lower-limit upper-limit))
   1563     (function           . (&optional arg-typespec value-typespec))
   1564     (integer            . (&optional lower-limit upper-limit))
   1565     (long-float         . (&optional lower-limit upper-limit))
   1566     (member             . (&rest eql-objects))
   1567     (mod                . (n))
   1568     (not                . (type-specifier))
   1569     (or                 . (&rest type-specifiers))
   1570     (rational           . (&optional lower-limit upper-limit))
   1571     (real               . (&optional lower-limit upper-limit))
   1572     (satisfies          . (predicate-symbol))
   1573     (short-float        . (&optional lower-limit upper-limit))
   1574     (signed-byte        . (&optional size))
   1575     (simple-array       . (&optional element-type dimension-spec))
   1576     (simple-base-string . (&optional size))
   1577     (simple-bit-vector  . (&optional size))
   1578     (simple-string      . (&optional size))
   1579     (single-float       . (&optional lower-limit upper-limit))
   1580     (simple-vector      . (&optional size))
   1581     (string             . (&optional size))
   1582     (unsigned-byte      . (&optional size))
   1583     (values             . (&rest typespecs))
   1584     (vector             . (&optional element-type size))
   1585     ))
   1586 
   1587 ;;; Heap dumps
   1588 
   1589 (definterface save-image (filename &optional restart-function)
   1590   "Save a heap image to the file FILENAME.
   1591 RESTART-FUNCTION, if non-nil, should be called when the image is loaded.")
   1592 
   1593 (definterface background-save-image (filename &key restart-function
   1594                                               completion-function)
   1595   "Request saving a heap image to the file FILENAME.
   1596 RESTART-FUNCTION, if non-nil, should be called when the image is loaded.
   1597 COMPLETION-FUNCTION, if non-nil, should be called after saving the image.")
   1598 
   1599 (defun deinit-log-output ()
   1600   ;; Can't hang on to an fd-stream from a previous session.
   1601   (setf (symbol-value (find-symbol "*LOG-OUTPUT*" 'slynk))
   1602         nil))
   1603 
   1604 
   1605 ;;;; Wrapping
   1606 
   1607 (definterface wrap (spec indicator &key before after replace)
   1608   "Intercept future calls to SPEC and surround them in callbacks.
   1609 
   1610 INDICATOR is a symbol identifying a particular wrapping, and is used
   1611 to differentiate between multiple wrappings.
   1612 
   1613 Implementations intercept calls to SPEC and call, in this order:
   1614 
   1615 * the BEFORE callback, if it's provided, with a single argument set to
   1616   the list of arguments passed to the intercepted call;
   1617 
   1618 * the original definition of SPEC recursively honouring any wrappings
   1619   previously established under different values of INDICATOR. If the
   1620   compatible function REPLACE is provided, call that instead.
   1621 
   1622 * the AFTER callback, if it's provided, with a single set to the list
   1623   of values returned by the previous call, or, if that call exited
   1624   non-locally, a single descriptive symbol, like :EXITED-NON-LOCALLY.
   1625 
   1626 The return value of implementation should be the
   1627 implementation-specific function object that SPEC describes, suitable
   1628 to be passed to the FIND-SOURCE-LOCATION interface."
   1629   (declare (ignore indicator))
   1630   (assert (symbolp spec) nil
   1631           "The default implementation for WRAP allows only simple names")
   1632   (assert (null (get spec 'sly-wrap)) nil
   1633           "The default implementation for WRAP allows a single wrapping")
   1634   (let* ((saved (symbol-function spec))
   1635          (replacement (lambda (&rest args)
   1636                         (let (retlist completed)
   1637                           (unwind-protect
   1638                                (progn
   1639                                  (when before
   1640                                    (funcall before args))
   1641                                  (setq retlist (multiple-value-list
   1642                                                 (apply (or replace
   1643                                                            saved) args)))
   1644                                  (setq completed t)
   1645                                  (values-list retlist))
   1646                             (when after
   1647                               (funcall after (if completed
   1648                                                  retlist
   1649                                                  :exited-non-locally))))))))
   1650     (setf (get spec 'sly-wrap) (list saved replacement))
   1651     (setf (symbol-function spec) replacement)
   1652     saved))
   1653 
   1654 (definterface unwrap (spec indicator)
   1655   "Remove from SPEC any wrappings tagged with INDICATOR."
   1656   (if (wrapped-p spec indicator)
   1657       (setf (symbol-function spec) (first (get spec 'sly-wrap)))
   1658       (cerror "All right, so I did"
   1659               "Hmmm, ~a is not correctly wrapped, you probably redefined it"
   1660               spec))
   1661   (setf (get spec 'sly-wrap) nil)
   1662   spec)
   1663 
   1664 (definterface wrapped-p (spec indicator)
   1665   "Returns true if SPEC is wrapped with INDICATOR."
   1666   (declare (ignore indicator))
   1667   (and (symbolp spec)
   1668        (let ((prop-value (get spec 'sly-wrap)))
   1669          (cond ((and prop-value
   1670                      (not (eq (second prop-value)
   1671                               (symbol-function spec))))
   1672                 (warn "~a appears to be incorrectly wrapped" spec)
   1673                 nil)
   1674                (prop-value t)
   1675                (t nil)))))