dotemacs

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

slynk-backend.lisp (60504B)


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