1 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; This software is derived from software originally released by Xerox
5 ;;;; Corporation. Copyright and release statements follow. Later modifications
6 ;;;; to the software are in the public domain and are provided with
7 ;;;; absolutely no warranty. See the COPYING and CREDITS files for more
10 ;;;; copyright information from original PCL sources:
12 ;;;; Copyright (c) 1985, 1986, 1987, 1988, 1989, 1990 Xerox Corporation.
13 ;;;; All rights reserved.
15 ;;;; Use and copying of this software and preparation of derivative works based
16 ;;;; upon this software are permitted. Any distribution of this software or
17 ;;;; derivative works must comply with all applicable United States export
20 ;;;; This software is made available AS IS, and Xerox Corporation makes no
21 ;;;; warranty about the software, its performance or its conformity to any
26 ;;;; DEFCLASS macro and close personal friends
28 ;;; ANSI says (Macro DEFCLASS, section 7.7) that DEFCLASS, if it
29 ;;; "appears as a top level form, the compiler must make the class
30 ;;; name be recognized as a valid type name in subsequent declarations
31 ;;; (as for deftype) and be recognized as a valid class name for
32 ;;; defmethod parameter specializers and for use as the :metaclass
33 ;;; option of a subsequent defclass."
34 (defun preinform-compiler-about-class-type (name)
35 ;; Unless the type system already has an actual type attached to
36 ;; NAME (in which case (1) writing a placeholder value over that
37 ;; actual type as a compile-time side-effect would probably be a bad
38 ;; idea and (2) anyway we don't need to modify it in order to make
39 ;; NAME be recognized as a valid type name)
40 (unless (info :type :kind name)
41 ;; Tell the compiler to expect a class with the given NAME, by
42 ;; writing a kind of minimal placeholder type information. This
43 ;; placeholder will be overwritten later when the class is defined.
44 (setf (info :type :kind name) :forthcoming-defclass-type))
47 ;;; state for the current DEFCLASS expansion
48 (defvar *initfunctions-for-this-defclass*)
49 (defvar *readers-for-this-defclass*)
50 (defvar *writers-for-this-defclass*)
51 (defvar *slot-names-for-this-defclass*)
53 ;;; Like the DEFMETHOD macro, the expansion of the DEFCLASS macro is
54 ;;; fixed. DEFCLASS always expands into a call to LOAD-DEFCLASS. Until
55 ;;; the meta-braid is set up, LOAD-DEFCLASS has a special definition
56 ;;; which simply collects all class definitions up, when the metabraid
57 ;;; is initialized it is done from those class definitions.
59 ;;; After the metabraid has been setup, and the protocol for defining
60 ;;; classes has been defined, the real definition of LOAD-DEFCLASS is
61 ;;; installed by the file std-class.lisp
62 (defmacro defclass (name %direct-superclasses %direct-slots &rest %options)
63 (let ((supers (copy-tree %direct-superclasses))
64 (slots (copy-tree %direct-slots))
65 (options (copy-tree %options)))
66 (let ((metaclass 'standard-class))
67 (dolist (option options)
68 (if (not (listp option))
69 (error "~S is not a legal defclass option." option)
70 (when (eq (car option) :metaclass)
71 (unless (legal-class-name-p (cadr option))
72 (error "The value of the :metaclass option (~S) is not a~%~
77 (cl:standard-class 'standard-class)
78 (cl:structure-class 'structure-class)
80 (setf options (remove option options))
83 (let ((*initfunctions-for-this-defclass* ())
84 (*readers-for-this-defclass* ()) ;Truly a crock, but we got
85 (*writers-for-this-defclass* ()) ;to have it to live nicely.
86 (*slot-names-for-this-defclass* ()))
87 (let ((canonical-slots
88 (mapcar (lambda (spec)
89 (canonicalize-slot-specification name spec))
92 (mapcar (lambda (option)
93 (canonicalize-defclass-option name option))
95 ;; DEFSTRUCT-P should be true if the class is defined
96 ;; with a metaclass STRUCTURE-CLASS, so that a DEFSTRUCT
97 ;; is compiled for the class.
98 (defstruct-p (and (eq *boot-state* 'complete)
99 (let ((mclass (find-class metaclass nil)))
103 *the-class-structure-class*))))))
106 ,@(mapcar (lambda (x)
107 `(declaim (ftype (function (t) t) ,x)))
108 *readers-for-this-defclass*)
109 ,@(mapcar (lambda (x)
110 `(declaim (ftype (function (t t) t) ,x)))
111 *writers-for-this-defclass*)
112 ,@(mapcar (lambda (x)
113 `(declaim (ftype (function (t) t)
114 ,(slot-reader-symbol x)
115 ,(slot-boundp-symbol x))
116 (ftype (function (t t) t)
117 ,(slot-writer-symbol x))))
118 *slot-names-for-this-defclass*)
119 (let ,(mapcar #'cdr *initfunctions-for-this-defclass*)
120 (load-defclass ',name
123 (list ,@canonical-slots)
124 (list ,@(apply #'append
126 '(:from-defclass-p t))
127 other-initargs)))))))
130 ;; FIXME: (YUK!) Why do we do this? Because in order
131 ;; to make the defstruct form, we need to know what
132 ;; the accessors for the slots are, so we need
133 ;; already to have hooked into the CLOS machinery.
135 ;; There may be a better way to do this: it would
136 ;; involve knowing enough about PCL to ask "what
137 ;; will my slot names and accessors be"; failing
138 ;; this, we currently just evaluate the whole
139 ;; kaboodle, and then use CLASS-DIRECT-SLOTS. --
142 (let* ((include (or (and supers
143 (fix-super (car supers)))
144 (and (not (eq name 'structure-object))
145 *the-class-structure-object*)))
146 (defstruct-form (make-structure-class-defstruct-form
147 name (class-direct-slots (find-class name)) include)))
149 (eval-when (:compile-toplevel :load-toplevel :execute)
150 ,defstruct-form) ; really compile the defstruct-form
151 (eval-when (:compile-toplevel :load-toplevel :execute)
154 ;; By telling the type system at compile time about
155 ;; the existence of a class named NAME, we can avoid
156 ;; various bogus warnings about "type isn't defined yet"
157 ;; for code elsewhere in the same file which uses
158 ;; the name of the type.
160 ;; We only need to do this at compile time, because
161 ;; at load and execute time we write the actual
162 ;; full-blown class, so the "a class of this name is
163 ;; coming" note we write here would be irrelevant.
164 (eval-when (:compile-toplevel)
165 (preinform-compiler-about-class-type ',name))
166 ,defclass-form))))))))
168 (defun make-initfunction (initform)
169 (cond ((or (eq initform t)
170 (equal initform ''t))
171 '(function constantly-t))
172 ((or (eq initform nil)
173 (equal initform ''nil))
174 '(function constantly-nil))
175 ((or (eql initform 0)
176 (equal initform ''0))
177 '(function constantly-0))
179 (let ((entry (assoc initform *initfunctions-for-this-defclass*
182 (setq entry (list initform
184 `(function (lambda () ,initform))))
185 (push entry *initfunctions-for-this-defclass*))
188 (defun canonicalize-slot-specification (class-name spec)
189 (cond ((and (symbolp spec)
190 (not (keywordp spec))
191 (not (memq spec '(t nil))))
192 (push spec *slot-names-for-this-defclass*)
195 (error "~S is not a legal slot specification." spec))
197 (push (car spec) *slot-names-for-this-defclass*)
198 `'(:name ,(car spec)))
200 (error "In DEFCLASS ~S, the slot specification ~S is obsolete.~%~
202 class-name spec (list (car spec) :initform (cadr spec))))
204 (let* ((name (pop spec))
208 (unsupplied (list nil))
209 (initform (getf spec :initform unsupplied)))
210 (push name *slot-names-for-this-defclass*)
211 (doplist (key val) spec
213 (:accessor (push val readers)
214 (push `(setf ,val) writers))
215 (:reader (push val readers))
216 (:writer (push val writers))
217 (:initarg (push val initargs))))
218 (loop (unless (remf spec :accessor) (return)))
219 (loop (unless (remf spec :reader) (return)))
220 (loop (unless (remf spec :writer) (return)))
221 (loop (unless (remf spec :initarg) (return)))
222 (setq *writers-for-this-defclass*
223 (append writers *writers-for-this-defclass*))
224 (setq *readers-for-this-defclass*
225 (append readers *readers-for-this-defclass*))
226 (setq spec `(:name ',name
231 (if (eq initform unsupplied)
233 `(list* :initfunction ,(make-initfunction initform) ,@spec))))))
235 (defun canonicalize-defclass-option (class-name option)
236 (declare (ignore class-name))
239 (let ((canonical ()))
240 (let (key val (tail (cdr option)))
241 (loop (when (null tail) (return nil))
244 (push ``(,',key ,,(make-initfunction val) ,',val) canonical))
245 `(:direct-default-initargs (list ,@(nreverse canonical))))))
247 `(',(car option) ',(cadr option)))
249 `(',(car option) ',(cdr option)))))
251 ;;; This is the early definition of LOAD-DEFCLASS. It just collects up
252 ;;; all the class definitions in a list. Later, in braid1.lisp, these
253 ;;; are actually defined.
255 ;;; Each entry in *EARLY-CLASS-DEFINITIONS* is an EARLY-CLASS-DEFINITION.
256 (defparameter *early-class-definitions* ())
258 (defun early-class-definition (class-name)
259 (or (find class-name *early-class-definitions* :key #'ecd-class-name)
260 (error "~S is not a class in *early-class-definitions*." class-name)))
262 (defun make-early-class-definition
263 (name source metaclass
264 superclass-names canonical-slots other-initargs)
265 (list 'early-class-definition
266 name source metaclass
267 superclass-names canonical-slots other-initargs))
269 (defun ecd-class-name (ecd) (nth 1 ecd))
270 (defun ecd-source (ecd) (nth 2 ecd))
271 (defun ecd-metaclass (ecd) (nth 3 ecd))
272 (defun ecd-superclass-names (ecd) (nth 4 ecd))
273 (defun ecd-canonical-slots (ecd) (nth 5 ecd))
274 (defun ecd-other-initargs (ecd) (nth 6 ecd))
276 (defvar *early-class-slots* nil)
278 (defun canonical-slot-name (canonical-slot)
279 (getf canonical-slot :name))
281 (defun early-class-slots (class-name)
282 (cdr (or (assoc class-name *early-class-slots*)
283 (let ((a (cons class-name
284 (mapcar #'canonical-slot-name
285 (early-collect-inheritance class-name)))))
286 (push a *early-class-slots*)
289 (defun early-class-size (class-name)
290 (length (early-class-slots class-name)))
292 (defun early-collect-inheritance (class-name)
293 ;;(declare (values slots cpl default-initargs direct-subclasses))
294 (let ((cpl (early-collect-cpl class-name)))
295 (values (early-collect-slots cpl)
297 (early-collect-default-initargs cpl)
299 (dolist (definition *early-class-definitions*)
300 (when (memq class-name (ecd-superclass-names definition))
301 (push (ecd-class-name definition) collect)))
302 (nreverse collect)))))
304 (defun early-collect-slots (cpl)
305 (let* ((definitions (mapcar #'early-class-definition cpl))
306 (super-slots (mapcar #'ecd-canonical-slots definitions))
307 (slots (apply #'append (reverse super-slots))))
309 (let ((name1 (canonical-slot-name s1)))
310 (dolist (s2 (cdr (memq s1 slots)))
311 (when (eq name1 (canonical-slot-name s2))
312 (error "More than one early class defines a slot with the~%~
313 name ~S. This can't work because the bootstrap~%~
314 object system doesn't know how to compute effective~%~
319 (defun early-collect-cpl (class-name)
321 (let* ((definition (early-class-definition c))
322 (supers (ecd-superclass-names definition)))
324 (apply #'append (mapcar #'early-collect-cpl supers))))))
325 (remove-duplicates (walk class-name) :from-end nil :test #'eq)))
327 (defun early-collect-default-initargs (cpl)
328 (let ((default-initargs ()))
329 (dolist (class-name cpl)
330 (let* ((definition (early-class-definition class-name))
331 (others (ecd-other-initargs definition)))
332 (loop (when (null others) (return nil))
333 (let ((initarg (pop others)))
334 (unless (eq initarg :direct-default-initargs)
335 (error "~@<The defclass option ~S is not supported by ~
336 the bootstrap object system.~:@>"
338 (setq default-initargs
339 (nconc default-initargs (reverse (pop others)))))))
340 (reverse default-initargs)))
342 (defun !bootstrap-slot-index (class-name slot-name)
343 (or (position slot-name (early-class-slots class-name))
344 (error "~S not found" slot-name)))
346 ;;; !BOOTSTRAP-GET-SLOT and !BOOTSTRAP-SET-SLOT are used to access and
347 ;;; change the values of slots during bootstrapping. During
348 ;;; bootstrapping, there are only two kinds of objects whose slots we
349 ;;; need to access, CLASSes and SLOT-DEFINITIONs. The first argument
350 ;;; to these functions tells whether the object is a CLASS or a
353 ;;; Note that the way this works it stores the slot in the same place
354 ;;; in memory that the full object system will expect to find it
355 ;;; later. This is critical to the bootstrapping process, the whole
356 ;;; changeover to the full object system is predicated on this.
358 ;;; One important point is that the layout of standard classes and
359 ;;; standard slots must be computed the same way in this file as it is
360 ;;; by the full object system later.
361 (defmacro !bootstrap-get-slot (type object slot-name)
362 `(clos-slots-ref (get-slots ,object)
363 (!bootstrap-slot-index ,type ,slot-name)))
364 (defun !bootstrap-set-slot (type object slot-name new-value)
365 (setf (!bootstrap-get-slot type object slot-name) new-value))
367 (defun early-class-name (class)
368 (!bootstrap-get-slot 'class class 'name))
370 (defun early-class-precedence-list (class)
371 (!bootstrap-get-slot 'pcl-class class 'class-precedence-list))
373 (defun early-class-name-of (instance)
374 (early-class-name (class-of instance)))
376 (defun early-class-slotds (class)
377 (!bootstrap-get-slot 'slot-class class 'slots))
379 (defun early-slot-definition-name (slotd)
380 (!bootstrap-get-slot 'standard-effective-slot-definition slotd 'name))
382 (defun early-slot-definition-location (slotd)
383 (!bootstrap-get-slot 'standard-effective-slot-definition slotd 'location))
385 (defun early-accessor-method-slot-name (method)
386 (!bootstrap-get-slot 'standard-accessor-method method 'slot-name))
388 (unless (fboundp 'class-name-of)
389 (setf (symbol-function 'class-name-of)
390 (symbol-function 'early-class-name-of)))
391 (unintern 'early-class-name-of)
393 (defun early-class-direct-subclasses (class)
394 (!bootstrap-get-slot 'class class 'direct-subclasses))
396 (declaim (notinline load-defclass))
397 (defun load-defclass (name metaclass supers canonical-slots canonical-options)
398 (setq supers (copy-tree supers)
399 canonical-slots (copy-tree canonical-slots)
400 canonical-options (copy-tree canonical-options))
402 (make-early-class-definition name
409 (find name *early-class-definitions* :key #'ecd-class-name)))
410 (setq *early-class-definitions*
411 (cons ecd (remove existing *early-class-definitions*)))