;; TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE
;; SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
-;; $Id: proxy.lisp,v 1.28 2006/02/06 18:12:19 espen Exp $
+;; $Id: proxy.lisp,v 1.33 2006/02/15 09:45:41 espen Exp $
(in-package "GLIB")
(boundp :reader slot-definition-boundp :initarg :boundp)))
(defclass direct-special-slot-definition (standard-direct-slot-definition)
- ())
+ ((special :initarg :special :accessor slot-definition-special)))
(defclass effective-special-slot-definition (standard-effective-slot-definition)
- ()))
+ ((special :initarg :special :accessor slot-definition-special))))
(defvar *unbound-marker* (gensym "UNBOUND-MARKER-"))
(slot-value object slot)
default)))
-(defmethod initialize-instance ((slotd effective-special-slot-definition) &rest initargs)
- (declare (ignore initargs))
- (call-next-method)
- (setf (slot-value slotd 'allocation) :instance))
-
(defmethod direct-slot-definition-class ((class virtual-slots-class) &rest initargs)
- (case (getf initargs :allocation)
- (:virtual (find-class 'direct-virtual-slot-definition))
- (:special (find-class 'direct-special-slot-definition))
- (t (call-next-method))))
+ (cond
+ ((eq (getf initargs :allocation) :virtual)
+ (find-class 'direct-virtual-slot-definition))
+ ((getf initargs :special)
+ (find-class 'direct-special-slot-definition))
+ (t (call-next-method))))
(defmethod effective-slot-definition-class ((class virtual-slots-class) &rest initargs)
- (case (getf initargs :allocation)
- (:virtual (find-class 'effective-virtual-slot-definition))
- (:special (find-class 'effective-special-slot-definition))
- (t (call-next-method))))
+ (cond
+ ((eq (getf initargs :allocation) :virtual)
+ (find-class 'effective-virtual-slot-definition))
+ ((getf initargs :special)
+ (find-class 'effective-special-slot-definition))
+ (t (call-next-method))))
(defmethod initialize-internal-slot-functions ((slotd effective-virtual-slot-definition))
(slot-value slotd 'reader-function)
#'(lambda (object)
(declare (ignore object))
- (error "Can't read slot: ~A" (slot-definition-name slotd)))
+ (error "Slot is not readable: ~A" (slot-definition-name slotd)))
(slot-value slotd 'boundp-function)
#'(lambda (object) (declare (ignore object)) nil))
(setf
(slot-value slotd 'writer-function)
(if (not (slot-boundp slotd 'setter))
- #'(lambda (object)
- (declare (ignore object))
- (error "Can't set slot: ~A" (slot-definition-name slotd)))
+ #'(lambda (value object)
+ (declare (ignore value object))
+ (error "Slot is not writable: ~A" (slot-definition-name slotd)))
(with-slots (setter) slotd
(etypecase setter
(function setter)
(slot-definition-type slotd))))
(funcall writer (foreign-location object) value)))))))))
- (initialize-internal-slot-gfs (slot-definition-name slotd)))
+ #-sbcl>=0.9.8(initialize-internal-slot-gfs (slot-definition-name slotd)))
nil)
(defmethod compute-effective-slot-definition-initargs ((class virtual-slots-class) direct-slotds)
- (if (typep (first direct-slotds) 'direct-virtual-slot-definition)
- (let ((initargs ()))
- (let ((getter (most-specific-slot-value direct-slotds 'getter)))
- (unless (eq getter *unbound-marker*)
- (setf (getf initargs :getter) getter)))
- (let ((setter (most-specific-slot-value direct-slotds 'setter)))
- (unless (eq setter *unbound-marker*)
- (setf (getf initargs :setter) setter)))
- (let ((unbound (most-specific-slot-value direct-slotds 'unbound)))
- (unless (eq unbound *unbound-marker*)
- (setf (getf initargs :unbound) unbound)))
- (let ((boundp (most-specific-slot-value direct-slotds 'boundp)))
- (unless (eq boundp *unbound-marker*)
- (setf (getf initargs :boundp) boundp)))
- (nconc initargs (call-next-method)))
- (call-next-method)))
+ (typecase (first direct-slotds)
+ (direct-virtual-slot-definition
+ (let ((initargs ()))
+ (let ((getter (most-specific-slot-value direct-slotds 'getter)))
+ (unless (eq getter *unbound-marker*)
+ (setf (getf initargs :getter) getter)))
+ (let ((setter (most-specific-slot-value direct-slotds 'setter)))
+ (unless (eq setter *unbound-marker*)
+ (setf (getf initargs :setter) setter)))
+ (let ((unbound (most-specific-slot-value direct-slotds 'unbound)))
+ (unless (eq unbound *unbound-marker*)
+ (setf (getf initargs :unbound) unbound)))
+ (let ((boundp (most-specific-slot-value direct-slotds 'boundp)))
+ (unless (eq boundp *unbound-marker*)
+ (setf (getf initargs :boundp) boundp)))
+ (nconc initargs (call-next-method))))
+ (direct-special-slot-definition
+ (append '(:special t) (call-next-method)))
+ (t (call-next-method))))
(defmethod slot-value-using-class
t)
+(defmethod slot-definition-special ((slotd standard-direct-slot-definition))
+ (declare (ignore slotd))
+ nil)
+
+(defmethod slot-definition-special ((slotd standard-effective-slot-definition))
+ (declare (ignore slotd))
+ nil)
+
+
;;;; Proxy cache
-(internal *instance-cache*)
(defvar *instance-cache* (make-hash-table :test #'eql))
(defun cache-instance (instance &optional (weak-ref t))
*instance-cache*)
instances))
+;; Instances that gets invalidated tend to be short lived, but created
+;; in large numbers. So we're keeping them in a hash table to be able
+;; to reuse them (and thus reduce consing)
+(defvar *invalidated-instance-cache* (make-hash-table :test #'eql))
+
+(defun cache-invalidated-instance (instance)
+ (push instance
+ (gethash (class-of instance) *invalidated-instance-cache*)))
+
+(defun find-invalidated-instance (class)
+ (when (gethash class *invalidated-instance-cache*)
+ (pop (gethash class *invalidated-instance-cache*))))
+
+(defun list-invalidated-instances ()
+ (let ((instances ()))
+ (maphash #'(lambda (location ref)
+ (declare (ignore location))
+ (push ref instances))
+ *invalidated-instance-cache*)
+ instances))
+
;;;; Proxy for alien instances
;; TODO: add a ref-counted-proxy subclass
(defclass proxy ()
- ((location :allocation :special :reader foreign-location :type pointer))
+ ((location :special t :type pointer))
(:metaclass virtual-slots-class))
(defgeneric instance-finalizer (object))
(defgeneric reference-foreign (class location))
(defgeneric unreference-foreign (class location))
(defgeneric invalidate-instance (object))
+(defgeneric allocate-foreign (object &key &allow-other-keys))
+
+(defun foreign-location (instance)
+ (slot-value instance 'location))
+
+(defun (setf foreign-location) (location instance)
+ (setf (slot-value instance 'location) location))
+
+(defun proxy-valid-p (instance)
+ (slot-boundp instance 'location))
(defmethod reference-foreign ((name symbol) location)
(reference-foreign (find-class name) location))
(format stream "at 0x~X" (sap-int (foreign-location instance)))
(write-string "at \"unbound\"" stream))))
-(defmethod initialize-instance :around ((instance proxy) &rest initargs)
- (declare (ignore initargs))
+(defmethod initialize-instance :around ((instance proxy) &rest initargs &key &allow-other-keys)
+ (setf
+ (foreign-location instance)
+ (apply #'allocate-foreign instance initargs))
(prog1
(call-next-method)
(cache-instance instance)
(remove-cached-instance location)
(unreference-foreign class location))))
+;; Any reference to the foreign object the instance may have held
+;; should be released before this method is invoked
(defmethod invalidate-instance ((instance proxy))
(remove-cached-instance (foreign-location instance))
- (slot-makunbound instance 'location))
+ (slot-makunbound instance 'location)
+ (cancel-finalization instance)
+ (cache-invalidated-instance instance))
;;;; Metaclass used for subclasses of proxy
(defgeneric most-specific-proxy-superclass (class))
(defgeneric direct-proxy-superclass (class))
-(defgeneric compute-foreign-size (class))
(eval-when (:compile-toplevel :load-toplevel :execute)
((size :reader foreign-size)))
(defclass direct-alien-slot-definition (direct-virtual-slot-definition)
- ((allocation :initform :alien)
- (offset :reader slot-definition-offset :initarg :offset)))
+ ((offset :reader slot-definition-offset :initarg :offset))
+ (:default-initargs :allocation :alien))
(defclass effective-alien-slot-definition (effective-virtual-slot-definition)
((offset :reader slot-definition-offset :initarg :offset)))
(defmethod compute-effective-slot-definition-initargs ((class proxy-class) direct-slotds)
- (if (eq (most-specific-slot-value direct-slotds 'allocation) :alien)
+ (if (eq (slot-definition-allocation (first direct-slotds)) :alien)
(nconc
(list :offset (most-specific-slot-value direct-slotds 'offset))
(call-next-method))
(call-next-method))
- (defmethod compute-foreign-size ((class proxy-class))
- nil)
-
;; TODO: call some C code to detect this a compile time
(defconstant +struct-alignmen+ 4)
do (setf (slot-value slotd 'offset) offset))))
(call-next-method))
- (defmethod compute-slots :after ((class proxy-class))
- (when (and (class-finalized-p class) (not (slot-boundp class 'size)))
- (let ((size (compute-foreign-size class)))
- (when size
- (setf (slot-value class 'size) size)))))
-
(defmethod validate-superclass ((class proxy-class) (super standard-class))
(subtypep (class-name super) 'proxy))
(apply #'make-proxy-instance (find-class class) location initargs))
(defmethod make-proxy-instance ((class proxy-class) location &key weak)
- (let ((instance (allocate-instance class)))
- (setf (slot-value instance 'location) location)
+ (let ((instance
+ (or
+ (find-invalidated-instance class)
+ (allocate-instance class))))
+ (setf (foreign-location instance) location)
(unless weak
(finalize instance (instance-finalizer instance)))
instance))
(:metaclass proxy-class)
(:size 0))
-(defmethod initialize-instance ((struct struct) &rest initargs)
+(defmethod allocate-foreign ((struct struct) &rest initargs)
(declare (ignore initargs))
- (unless (slot-boundp struct 'location)
- (let ((size (foreign-size (class-of struct))))
- (if (zerop size)
- (error "~A has zero size" (class-of struct))
- (setf (slot-value struct 'location) (allocate-memory size)))))
- (call-next-method))
+ (let ((size (foreign-size (class-of struct))))
+ (if (zerop size)
+ (error "~A has zero size" (class-of struct))
+ (allocate-memory size))))
;;;; Metaclasses used for subclasses of struct
(defmethod unreference-foreign ((class struct-class) location)
(deallocate-memory location))
-(defmethod compute-foreign-size ((class struct-class))
- (let ((size (loop
- for slotd in (class-slots class)
- when (eq (slot-definition-allocation slotd) :alien)
- maximize (+
- (slot-definition-offset slotd)
- (size-of (slot-definition-type slotd))))))
- (+ size (mod size +struct-alignmen+))))
+(defmethod compute-slots :around ((class struct-class))
+ (let ((slots (call-next-method)))
+ (when (and
+ #-sbcl>=0.9.8(class-finalized-p class)
+ (not (slot-boundp class 'size)))
+ (let ((size (loop
+ for slotd in slots
+ when (eq (slot-definition-allocation slotd) :alien)
+ maximize (+
+ (slot-definition-offset slotd)
+ (size-of (slot-definition-type slotd))))))
+ (setf (slot-value class 'size) (+ size (mod size +struct-alignmen+)))))
+ slots))
(defmethod reader-function ((class struct-class) &rest args)
(declare (ignore args))