X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=src%2Fpcl%2Fdefclass.lisp;h=33bfd0b1a3024063326c7942436f413e21d406b9;hb=0f3a5f2e8886d18d0b4f6485c38a42be629422ae;hp=ed10b5fafad637c04d765c916967924e568b6b5a;hpb=203c15eefffd996fd20bd28d461ea1aa3865dbbe;p=sbcl.git diff --git a/src/pcl/defclass.lisp b/src/pcl/defclass.lisp index ed10b5f..33bfd0b 100644 --- a/src/pcl/defclass.lisp +++ b/src/pcl/defclass.lisp @@ -23,19 +23,14 @@ (in-package "SB-PCL") +;;;; DEFCLASS macro and close personal friends + +;;; state for the current DEFCLASS expansion +(defvar *initfunctions-for-this-defclass*) +(defvar *readers-for-this-defclass*) +(defvar *writers-for-this-defclass*) +(defvar *slot-names-for-this-defclass*) -(defun make-progn (&rest forms) - (let ((progn-form nil)) - (labels ((collect-forms (forms) - (unless (null forms) - (collect-forms (cdr forms)) - (if (and (listp (car forms)) - (eq (caar forms) 'progn)) - (collect-forms (cdar forms)) - (push (car forms) progn-form))))) - (collect-forms forms) - (cons 'progn progn-form)))) - ;;; Like the DEFMETHOD macro, the expansion of the DEFCLASS macro is ;;; fixed. DEFCLASS always expands into a call to LOAD-DEFCLASS. Until ;;; the meta-braid is set up, LOAD-DEFCLASS has a special definition @@ -44,186 +39,298 @@ ;;; ;;; After the metabraid has been setup, and the protocol for defining ;;; classes has been defined, the real definition of LOAD-DEFCLASS is -;;; installed by the file defclass.lisp -(defmacro defclass (name direct-superclasses direct-slots &rest options) - (expand-defclass name direct-superclasses direct-slots options)) - -(defun expand-defclass (name supers slots options) - (setq supers (copy-tree supers) - slots (copy-tree slots) - options (copy-tree options)) - (let ((metaclass 'standard-class)) - (dolist (option options) - (if (not (listp option)) - (error "~S is not a legal defclass option." option) - (when (eq (car option) ':metaclass) - (unless (legal-class-name-p (cadr option)) - (error "The value of the :metaclass option (~S) is not a~%~ - legal class name." - (cadr option))) - (setq metaclass - (case (cadr option) - (cl:standard-class 'standard-class) - (cl:structure-class 'structure-class) - (t (cadr option)))) - (setf options (remove option options)) - (return t)))) - - (let ((*initfunctions* ()) - (*readers* ()) ;Truly a crock, but we got - (*writers* ())) ;to have it to live nicely. - (declare (special *initfunctions* *readers* *writers*)) - (let ((canonical-slots - (mapcar #'(lambda (spec) - (canonicalize-slot-specification name spec)) - slots)) - (other-initargs - (mapcar #'(lambda (option) - (canonicalize-defclass-option name option)) - options)) - (defstruct-p (and (eq *boot-state* 'complete) - (let ((mclass (find-class metaclass nil))) - (and mclass - (*subtypep - mclass - *the-class-structure-class*)))))) - (let ((defclass-form - `(progn - ,@(mapcar (lambda (x) - `(declaim (ftype (function (t) t) ,x))) - *readers*) - ,@(mapcar (lambda (x) - `(declaim (ftype (function (t t) t) ,x))) - *writers*) - (let ,(mapcar #'cdr *initfunctions*) - (load-defclass ',name - ',metaclass - ',supers - (list ,@canonical-slots) - (list ,@(apply #'append - (when defstruct-p - '(:from-defclass-p t)) - other-initargs))))))) - ;; FIXME: The way that we do things like (EVAL DEFCLASS-FORM) - ;; here is un-ANSI-Common-Lisp-y and leads to problems - ;; (like DEFUN for the type predicate being called more than - ;; once when we do DEFCLASS at the interpreter prompt), - ;; causing bogus style warnings. It would be better to - ;; rewrite this so that the macroexpansion looks like e.g. - ;; (PROGN - ;; (EVAL-WHEN (:COMPILE-TOPLEVEL :LOAD-TOPLEVEL :EXECUTE) - ;; (FROB1 ..)) - ;; (EVAL-WHEN (:LOAD-TOPLEVEL :EXECUTE) - ;; (FROB2 ..))) - (if defstruct-p - (progn - (eval defclass-form) ; Define the class now, so that.. - `(progn ; ..the defstruct can be compiled. - ,(class-defstruct-form (find-class name)) - ,defclass-form)) - (progn - (when (eq *boot-state* 'complete) - ;; FIXME: MNA (on sbcl-devel 2001-05-30) reported - ;; (if I understand correctly -- WHN) that this call - ;; is directly responsible for defining - ;; class-predicates which always return - ;; CONSTANTLY-NIL in the compile-time environment, - ;; and is indirectly responsible for bogus warnings - ;; about redefinitions when making definitions in - ;; the interpreter. I didn't like his fix (deleting - ;; the call) since I think the type system *should* - ;; be informed about class definitions here. And I'm - ;; not eager to look too deeply into this sort of - ;; done-too-many-times-in-the-interpreter problem - ;; right now, since it should be easier to make a - ;; clean fix when EVAL-WHEN is made more ANSI (as - ;; per the IR1 section in the BUGS file). But - ;; at some point this should be cleaned up. - (inform-type-system-about-std-class name)) - defclass-form))))))) +;;; installed by the file std-class.lisp +(defmacro defclass (&environment env name direct-superclasses direct-slots &rest options) + (let (*initfunctions-for-this-defclass* + *readers-for-this-defclass* ;Truly a crock, but we got + *writers-for-this-defclass* ;to have it to live nicely. + *slot-names-for-this-defclass*) + ;; FIXME: It would be nice to collect all errors from the + ;; expansion of a defclass and signal them in a single go. + (multiple-value-bind (metaclass canonical-options) + (canonize-defclass-options name options) + (let ((canonical-slots (canonize-defclass-slots name direct-slots env)) + ;; DEFSTRUCT-P should be true if the class is defined + ;; with a metaclass STRUCTURE-CLASS, so that a DEFSTRUCT + ;; is compiled for the class. + (defstruct-p (and (eq **boot-state** 'complete) + (let ((mclass (find-class metaclass nil))) + (and mclass + (*subtypep + mclass + *the-class-structure-class*)))))) + (let* ((defclass-form + `(let ,(mapcar #'cdr *initfunctions-for-this-defclass*) + (load-defclass ',name + ',metaclass + ',direct-superclasses + (list ,@canonical-slots) + (list ,@(apply #'append + (when defstruct-p + '(:from-defclass-p t)) + canonical-options)) + ',*readers-for-this-defclass* + ',*writers-for-this-defclass* + ',*slot-names-for-this-defclass* + (sb-c:source-location) + ',(safe-code-p env))))) + (if defstruct-p + (progn + ;; FIXME: (YUK!) Why do we do this? Because in order + ;; to make the defstruct form, we need to know what + ;; the accessors for the slots are, so we need already + ;; to have hooked into the CLOS machinery. + ;; + ;; There may be a better way to do this: it would + ;; involve knowing enough about PCL to ask "what will + ;; my slot names and accessors be"; failing this, we + ;; currently just evaluate the whole kaboodle, and + ;; then use CLASS-DIRECT-SLOTS. -- CSR, 2002-06-07 + (eval defclass-form) + (let* ((include (or (and direct-superclasses + (find-class (car direct-superclasses) nil)) + (and (not (eq name 'structure-object)) + *the-class-structure-object*))) + (defstruct-form (make-structure-class-defstruct-form + name (class-direct-slots (find-class name)) + include))) + `(progn + (eval-when (:compile-toplevel :load-toplevel :execute) + ,defstruct-form) ; really compile the defstruct-form + (eval-when (:compile-toplevel :load-toplevel :execute) + ,defclass-form)))) + `(progn + ;; By telling the type system at compile time about + ;; the existence of a class named NAME, we can avoid + ;; various bogus warnings about "type isn't defined yet" + ;; for code elsewhere in the same file which uses + ;; the name of the type. + ;; + ;; We only need to do this at compile time, because + ;; at load and execute time we write the actual + ;; full-blown class, so the "a class of this name is + ;; coming" note we write here would be irrelevant. + (eval-when (:compile-toplevel) + (%compiler-defclass ',name + ',*readers-for-this-defclass* + ',*writers-for-this-defclass* + ',*slot-names-for-this-defclass*)) + (eval-when (:load-toplevel :execute) + ,defclass-form)))))))) + +(defun canonize-defclass-options (class-name options) + (maplist (lambda (sublist) + (let ((option-name (first (pop sublist)))) + (when (member option-name sublist :key #'first :test #'eq) + (error 'simple-program-error + :format-control "Multiple ~S options in DEFCLASS ~S." + :format-arguments (list option-name class-name))))) + options) + (let (metaclass + default-initargs + documentation + canonized-options) + (dolist (option options) + (unless (listp option) + (error "~S is not a legal defclass option." option)) + (case (first option) + (:metaclass + (let ((maybe-metaclass (second option))) + (unless (and maybe-metaclass (legal-class-name-p maybe-metaclass)) + (error 'simple-program-error + :format-control "~@" + :format-arguments (list maybe-metaclass))) + (setf metaclass maybe-metaclass))) + (:default-initargs + (let (initargs arg-names) + (doplist (key val) (cdr option) + (when (member key arg-names :test #'eq) + (error 'simple-program-error + :format-control "~@" + :format-arguments (list key class-name))) + (push key arg-names) + (push ``(,',key ,',val ,,(make-initfunction val)) initargs)) + (setf default-initargs t) + (push `(:direct-default-initargs (list ,@(nreverse initargs))) + canonized-options))) + (:documentation + (unless (stringp (second option)) + (error "~S is not a legal :documentation value" (second option))) + (setf documentation t) + (push `(:documentation ,(second option)) canonized-options)) + (otherwise + (push `(',(car option) ',(cdr option)) canonized-options)))) + (unless default-initargs + (push '(:direct-default-initargs nil) canonized-options)) + (values (or metaclass 'standard-class) (nreverse canonized-options)))) + +(defun canonize-defclass-slots (class-name slots env) + (let (canonized-specs) + (dolist (spec slots) + (when (atom spec) + (setf spec (list spec))) + (when (and (cdr spec) (null (cddr spec))) + (error 'simple-program-error + :format-control "~@" + :format-arguments (list class-name spec + `(,(car spec) :initform ,(cadr spec))))) + (let* ((name (car spec)) + (plist (cdr spec)) + (readers ()) + (writers ()) + (initargs ()) + (others ()) + (unsupplied (list nil)) + (type t) + (initform unsupplied)) + (check-slot-name-for-defclass name class-name env) + (push name *slot-names-for-this-defclass*) + (flet ((note-reader (x) + (unless (symbolp x) + (error 'simple-program-error + :format-control "Slot reader name ~S for slot ~S in ~ + DEFCLASS ~S is not a symbol." + :format-arguments (list x name class-name))) + (push x readers) + (push x *readers-for-this-defclass*)) + (note-writer (x) + (push x writers) + (push x *writers-for-this-defclass*))) + (doplist (key val) plist + (case key + (:accessor (note-reader val) (note-writer `(setf ,val))) + (:reader (note-reader val)) + (:writer (note-writer val)) + (:initarg + (unless (symbolp val) + (error 'simple-program-error + :format-control "Slot initarg name ~S for slot ~S in ~ + DEFCLASS ~S is not a symbol." + :format-arguments (list val name class-name))) + (push val initargs)) + (otherwise + (when (member key '(:initform :allocation :type :documentation)) + (when (eq key :initform) + (setf initform val)) + (when (eq key :type) + (setf type val)) + (when (get-properties others (list key)) + (error 'simple-program-error + :format-control "Duplicate slot option ~S for slot ~ + ~S in DEFCLASS ~S." + :format-arguments (list key name class-name)))) + ;; For non-standard options multiple entries go in a list + (push val (getf others key)))))) + ;; Unwrap singleton lists (AMOP 5.4.2) + (do ((head others (cddr head))) + ((null head)) + (unless (cdr (second head)) + (setf (second head) (car (second head))))) + (let ((canon `(:name ',name :readers ',readers :writers ',writers + :initargs ',initargs ',others))) + (push (if (eq initform unsupplied) + `(list* ,@canon) + `(list* :initfunction ,(make-initfunction initform) + ,@canon)) + canonized-specs)))) + (nreverse canonized-specs))) + + +(defun check-slot-name-for-defclass (name class-name env) + (flet ((slot-name-illegal (reason) + (error 'simple-program-error + :format-control + (format nil "~~@" reason) + :format-arguments (list class-name name)))) + (cond ((not (symbolp name)) + (slot-name-illegal "not a symbol")) + ((keywordp name) + (slot-name-illegal "a keyword")) + ((constantp name env) + (slot-name-illegal "a constant")) + ((member name *slot-names-for-this-defclass* :test #'eq) + (error 'simple-program-error + :format-control "Multiple slots named ~S in DEFCLASS ~S." + :format-arguments (list name class-name)))))) (defun make-initfunction (initform) - (declare (special *initfunctions*)) (cond ((or (eq initform t) - (equal initform ''t)) - '(function constantly-t)) - ((or (eq initform nil) - (equal initform ''nil)) - '(function constantly-nil)) - ((or (eql initform 0) - (equal initform ''0)) - '(function constantly-0)) - (t - (let ((entry (assoc initform *initfunctions* :test #'equal))) - (unless entry - (setq entry (list initform - (gensym) - `(function (lambda () ,initform)))) - (push entry *initfunctions*)) - (cadr entry))))) - -(defun canonicalize-slot-specification (class-name spec) - (declare (special *readers* *writers*)) - (cond ((and (symbolp spec) - (not (keywordp spec)) - (not (memq spec '(t nil)))) - `'(:name ,spec)) - ((not (consp spec)) - (error "~S is not a legal slot specification." spec)) - ((null (cdr spec)) - `'(:name ,(car spec))) - ((null (cddr spec)) - (error "In DEFCLASS ~S, the slot specification ~S is obsolete.~%~ - Convert it to ~S" - class-name spec (list (car spec) :initform (cadr spec)))) - (t - (let* ((name (pop spec)) - (readers ()) - (writers ()) - (initargs ()) - (unsupplied (list nil)) - (initform (getf spec :initform unsupplied))) - (doplist (key val) spec - (case key - (:accessor (push val readers) - (push `(setf ,val) writers)) - (:reader (push val readers)) - (:writer (push val writers)) - (:initarg (push val initargs)))) - (loop (unless (remf spec :accessor) (return))) - (loop (unless (remf spec :reader) (return))) - (loop (unless (remf spec :writer) (return))) - (loop (unless (remf spec :initarg) (return))) - (setq *writers* (append writers *writers*)) - (setq *readers* (append readers *readers*)) - (setq spec `(:name ',name - :readers ',readers - :writers ',writers - :initargs ',initargs - ',spec)) - (if (eq initform unsupplied) - `(list* ,@spec) - `(list* :initfunction ,(make-initfunction initform) ,@spec)))))) - -(defun canonicalize-defclass-option (class-name option) - (declare (ignore class-name)) - (case (car option) - (:default-initargs - (let ((canonical ())) - (let (key val (tail (cdr option))) - (loop (when (null tail) (return nil)) - (setq key (pop tail) - val (pop tail)) - (push ``(,',key ,,(make-initfunction val) ,',val) canonical)) - `(':direct-default-initargs (list ,@(nreverse canonical)))))) - (:documentation - `(',(car option) ',(cadr option))) - (otherwise - `(',(car option) ',(cdr option))))) + (equal initform ''t)) + '(function constantly-t)) + ((or (eq initform nil) + (equal initform ''nil)) + '(function constantly-nil)) + ((or (eql initform 0) + (equal initform ''0)) + '(function constantly-0)) + (t + (let ((entry (assoc initform *initfunctions-for-this-defclass* + :test #'equal))) + (unless entry + (setq entry (list initform + (gensym) + `(function (lambda () + (declare (optimize + (sb-c:store-coverage-data 0))) + ,initform)))) + (push entry *initfunctions-for-this-defclass*)) + (cadr entry))))) + +(defun %compiler-defclass (name readers writers slots) + ;; ANSI says (Macro DEFCLASS, section 7.7) that DEFCLASS, if it + ;; "appears as a top level form, the compiler must make the class + ;; name be recognized as a valid type name in subsequent + ;; declarations (as for deftype) and be recognized as a valid class + ;; name for defmethod parameter specializers and for use as the + ;; :metaclass option of a subsequent defclass." + (preinform-compiler-about-class-type name) + (preinform-compiler-about-accessors readers writers slots)) + +(defun preinform-compiler-about-class-type (name) + ;; Unless the type system already has an actual type attached to + ;; NAME (in which case (1) writing a placeholder value over that + ;; actual type as a compile-time side-effect would probably be a bad + ;; idea and (2) anyway we don't need to modify it in order to make + ;; NAME be recognized as a valid type name) + (with-single-package-locked-error (:symbol name "proclaiming ~S as a class")) + (unless (info :type :kind name) + ;; Tell the compiler to expect a class with the given NAME, by + ;; writing a kind of minimal placeholder type information. This + ;; placeholder will be overwritten later when the class is defined. + (setf (info :type :kind name) :forthcoming-defclass-type)) + (values)) + +(defun preinform-compiler-about-accessors (readers writers slots) + (flet ((inform (name type) + ;; FIXME: This matches what PROCLAIM FTYPE does, except + ;; that :WHERE-FROM is :DEFINED, not :DECLARED, and should + ;; probably be factored into a common function -- eg. + ;; (%proclaim-ftype name declared-or-defined). + (when (eq (info :function :where-from name) :assumed) + (proclaim-as-fun-name name) + (note-name-defined name :function) + (setf (info :function :where-from name) :defined + (info :function :type name) type)))) + (let ((rtype (specifier-type '(function (t) t))) + (wtype (specifier-type '(function (t t) t)))) + (dolist (reader readers) + (inform reader rtype)) + (dolist (writer writers) + (inform writer wtype)) + (dolist (slot slots) + (inform (slot-reader-name slot) rtype) + (inform (slot-boundp-name slot) rtype) + (inform (slot-writer-name slot) wtype))))) -;;; This is the early definition of load-defclass. It just collects up -;;; all the class definitions in a list. Later, in the file -;;; braid1.lisp, these are actually defined. +;;; This is the early definition of LOAD-DEFCLASS. It just collects up +;;; all the class definitions in a list. Later, in braid1.lisp, these +;;; are actually defined. ;;; Each entry in *EARLY-CLASS-DEFINITIONS* is an EARLY-CLASS-DEFINITION. (defparameter *early-class-definitions* ()) @@ -233,14 +340,14 @@ (error "~S is not a class in *early-class-definitions*." class-name))) (defun make-early-class-definition - (name source metaclass - superclass-names canonical-slots other-initargs) + (name source-location metaclass + superclass-names canonical-slots other-initargs) (list 'early-class-definition - name source metaclass - superclass-names canonical-slots other-initargs)) + name source-location metaclass + superclass-names canonical-slots other-initargs)) (defun ecd-class-name (ecd) (nth 1 ecd)) -(defun ecd-source (ecd) (nth 2 ecd)) +(defun ecd-source-location (ecd) (nth 2 ecd)) (defun ecd-metaclass (ecd) (nth 3 ecd)) (defun ecd-superclass-names (ecd) (nth 4 ecd)) (defun ecd-canonical-slots (ecd) (nth 5 ecd)) @@ -253,11 +360,11 @@ (defun early-class-slots (class-name) (cdr (or (assoc class-name *early-class-slots*) - (let ((a (cons class-name - (mapcar #'canonical-slot-name - (early-collect-inheritance class-name))))) - (push a *early-class-slots*) - a)))) + (let ((a (cons class-name + (mapcar #'canonical-slot-name + (early-collect-inheritance class-name))))) + (push a *early-class-slots*) + a)))) (defun early-class-size (class-name) (length (early-class-slots class-name))) @@ -266,49 +373,50 @@ ;;(declare (values slots cpl default-initargs direct-subclasses)) (let ((cpl (early-collect-cpl class-name))) (values (early-collect-slots cpl) - cpl - (early-collect-default-initargs cpl) - (gathering1 (collecting) - (dolist (definition *early-class-definitions*) - (when (memq class-name (ecd-superclass-names definition)) - (gather1 (ecd-class-name definition)))))))) + cpl + (early-collect-default-initargs cpl) + (let (collect) + (dolist (definition *early-class-definitions*) + (when (memq class-name (ecd-superclass-names definition)) + (push (ecd-class-name definition) collect))) + (nreverse collect))))) (defun early-collect-slots (cpl) (let* ((definitions (mapcar #'early-class-definition cpl)) - (super-slots (mapcar #'ecd-canonical-slots definitions)) - (slots (apply #'append (reverse super-slots)))) + (super-slots (mapcar #'ecd-canonical-slots definitions)) + (slots (apply #'append (reverse super-slots)))) (dolist (s1 slots) (let ((name1 (canonical-slot-name s1))) - (dolist (s2 (cdr (memq s1 slots))) - (when (eq name1 (canonical-slot-name s2)) - (error "More than one early class defines a slot with the~%~ - name ~S. This can't work because the bootstrap~%~ - object system doesn't know how to compute effective~%~ - slots." - name1))))) + (dolist (s2 (cdr (memq s1 slots))) + (when (eq name1 (canonical-slot-name s2)) + (error "More than one early class defines a slot with the~%~ + name ~S. This can't work because the bootstrap~%~ + object system doesn't know how to compute effective~%~ + slots." + name1))))) slots)) (defun early-collect-cpl (class-name) (labels ((walk (c) - (let* ((definition (early-class-definition c)) - (supers (ecd-superclass-names definition))) - (cons c - (apply #'append (mapcar #'early-collect-cpl supers)))))) + (let* ((definition (early-class-definition c)) + (supers (ecd-superclass-names definition))) + (cons c + (apply #'append (mapcar #'early-collect-cpl supers)))))) (remove-duplicates (walk class-name) :from-end nil :test #'eq))) (defun early-collect-default-initargs (cpl) (let ((default-initargs ())) (dolist (class-name cpl) (let* ((definition (early-class-definition class-name)) - (others (ecd-other-initargs definition))) - (loop (when (null others) (return nil)) - (let ((initarg (pop others))) - (unless (eq initarg :direct-default-initargs) - (error "~@" - initarg))) - (setq default-initargs - (nconc default-initargs (reverse (pop others))))))) + (others (ecd-other-initargs definition))) + (loop (when (null others) (return nil)) + (let ((initarg (pop others))) + (unless (eq initarg :direct-default-initargs) + (error "~@" + initarg))) + (setq default-initargs + (nconc default-initargs (reverse (pop others))))))) (reverse default-initargs))) (defun !bootstrap-slot-index (class-name slot-name) @@ -332,7 +440,7 @@ ;;; by the full object system later. (defmacro !bootstrap-get-slot (type object slot-name) `(clos-slots-ref (get-slots ,object) - (!bootstrap-slot-index ,type ,slot-name))) + (!bootstrap-slot-index ,type ,slot-name))) (defun !bootstrap-set-slot (type object slot-name new-value) (setf (!bootstrap-get-slot type object slot-name) new-value)) @@ -340,7 +448,7 @@ (!bootstrap-get-slot 'class class 'name)) (defun early-class-precedence-list (class) - (!bootstrap-get-slot 'pcl-class class 'class-precedence-list)) + (!bootstrap-get-slot 'pcl-class class '%class-precedence-list)) (defun early-class-name-of (instance) (early-class-name (class-of instance))) @@ -354,34 +462,39 @@ (defun early-slot-definition-location (slotd) (!bootstrap-get-slot 'standard-effective-slot-definition slotd 'location)) +(defun early-slot-definition-info (slotd) + (!bootstrap-get-slot 'standard-effective-slot-definition slotd 'info)) + (defun early-accessor-method-slot-name (method) (!bootstrap-get-slot 'standard-accessor-method method 'slot-name)) (unless (fboundp 'class-name-of) (setf (symbol-function 'class-name-of) - (symbol-function 'early-class-name-of))) + (symbol-function 'early-class-name-of))) (unintern 'early-class-name-of) (defun early-class-direct-subclasses (class) (!bootstrap-get-slot 'class class 'direct-subclasses)) (declaim (notinline load-defclass)) -(defun load-defclass (name metaclass supers canonical-slots canonical-options) +(defun load-defclass (name metaclass supers canonical-slots canonical-options + readers writers slot-names source-location safe-p) + ;; SAFE-P is used by REAL-LOAD-DEFCLASS, but can be ignored here, since + ;; during the bootstrap we won't have (SAFETY 3). + (declare (ignore safe-p)) + (%compiler-defclass name readers writers slot-names) (setq supers (copy-tree supers) - canonical-slots (copy-tree canonical-slots) - canonical-options (copy-tree canonical-options)) - (when (eq metaclass 'standard-class) - (inform-type-system-about-std-class name)) + canonical-slots (copy-tree canonical-slots) + canonical-options (copy-tree canonical-options)) (let ((ecd - (make-early-class-definition name - *load-truename* - metaclass - supers - canonical-slots - canonical-options)) - (existing - (find name *early-class-definitions* :key #'ecd-class-name))) + (make-early-class-definition name + source-location + metaclass + supers + canonical-slots + canonical-options)) + (existing + (find name *early-class-definitions* :key #'ecd-class-name))) (setq *early-class-definitions* - (cons ecd (remove existing *early-class-definitions*))) + (cons ecd (remove existing *early-class-definitions*))) ecd)) -