0.7.1.19:
[sbcl.git] / src / pcl / defclass.lisp
1 ;;;; This software is part of the SBCL system. See the README file for
2 ;;;; more information.
3
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
8 ;;;; information.
9
10 ;;;; copyright information from original PCL sources:
11 ;;;;
12 ;;;; Copyright (c) 1985, 1986, 1987, 1988, 1989, 1990 Xerox Corporation.
13 ;;;; All rights reserved.
14 ;;;;
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
18 ;;;; control laws.
19 ;;;;
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
22 ;;;; specification.
23
24 (in-package "SB-PCL")
25 \f
26 ;;;; DEFCLASS macro and close personal friends
27
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))
45   (values))
46
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
52 ;;; Like the DEFMETHOD macro, the expansion of the DEFCLASS macro is
53 ;;; fixed. DEFCLASS always expands into a call to LOAD-DEFCLASS. Until
54 ;;; the meta-braid is set up, LOAD-DEFCLASS has a special definition
55 ;;; which simply collects all class definitions up, when the metabraid
56 ;;; is initialized it is done from those class definitions.
57 ;;;
58 ;;; After the metabraid has been setup, and the protocol for defining
59 ;;; classes has been defined, the real definition of LOAD-DEFCLASS is
60 ;;; installed by the file std-class.lisp
61 (defmacro defclass (name %direct-superclasses %direct-slots &rest %options)
62   (let ((supers  (copy-tree %direct-superclasses))
63         (slots   (copy-tree %direct-slots))
64         (options (copy-tree %options)))
65     (let ((metaclass 'standard-class))
66       (dolist (option options)
67         (if (not (listp option))
68           (error "~S is not a legal defclass option." option)
69           (when (eq (car option) :metaclass)
70             (unless (legal-class-name-p (cadr option))
71               (error "The value of the :metaclass option (~S) is not a~%~
72                       legal class name."
73                      (cadr option)))
74             (setq metaclass
75                     (case (cadr option)
76                       (cl:standard-class 'standard-class)
77                       (cl:structure-class 'structure-class)
78                       (t (cadr option))))
79             (setf options (remove option options))
80             (return t))))
81
82       (let ((*initfunctions-for-this-defclass* ())
83             (*readers-for-this-defclass* ()) ;Truly a crock, but we got
84             (*writers-for-this-defclass* ())) ;to have it to live nicely.
85         (let ((canonical-slots
86                 (mapcar (lambda (spec)
87                           (canonicalize-slot-specification name spec))
88                         slots))
89               (other-initargs
90                 (mapcar (lambda (option)
91                           (canonicalize-defclass-option name option))
92                         options))
93               ;; DEFSTRUCT-P should be true if the class is defined
94               ;; with a metaclass STRUCTURE-CLASS, so that a DEFSTRUCT
95               ;; is compiled for the class.
96               (defstruct-p (and (eq *boot-state* 'complete)
97                                 (let ((mclass (find-class metaclass nil)))
98                                   (and mclass
99                                        (*subtypep
100                                         mclass
101                                         *the-class-structure-class*))))))
102           (let ((defclass-form
103                   `(progn
104                      ,@(mapcar (lambda (x)
105                                  `(declaim (ftype (function (t) t) ,x)))
106                                *readers-for-this-defclass*)
107                      ,@(mapcar (lambda (x)
108                                  `(declaim (ftype (function (t t) t) ,x)))
109                                *writers-for-this-defclass*)
110                      (let ,(mapcar #'cdr *initfunctions-for-this-defclass*)
111                        (load-defclass ',name
112                                       ',metaclass
113                                       ',supers
114                                       (list ,@canonical-slots)
115                                       (list ,@(apply #'append
116                                                      (when defstruct-p
117                                                        '(:from-defclass-p t))
118                                                      other-initargs)))))))
119             (if defstruct-p
120                 (let* ((include (or (and supers
121                                          (fix-super (car supers)))
122                                     (and (not (eq name 'structure-object))
123                                          *the-class-structure-object*)))
124                        (defstruct-form (make-structure-class-defstruct-form
125                                         name slots include)))
126                   `(progn
127                      (eval-when (:compile-toplevel :load-toplevel :execute)
128                        ,defstruct-form) ; really compile the defstruct-form
129                      (eval-when (:compile-toplevel :load-toplevel :execute)
130                        ,defclass-form)))
131                 `(progn
132                    ;; By telling the type system at compile time about
133                    ;; the existence of a class named NAME, we can avoid
134                    ;; various bogus warnings about "type isn't defined yet"
135                    ;; for code elsewhere in the same file which uses
136                    ;; the name of the type.
137                    ;;
138                    ;; We only need to do this at compile time, because
139                    ;; at load and execute time we write the actual
140                    ;; full-blown class, so the "a class of this name is
141                    ;; coming" note we write here would be irrelevant.
142                    (eval-when (:compile-toplevel)
143                      (preinform-compiler-about-class-type ',name))
144                    ,defclass-form))))))))
145
146 (defun make-initfunction (initform)
147   (cond ((or (eq initform t)
148              (equal initform ''t))
149          '(function constantly-t))
150         ((or (eq initform nil)
151              (equal initform ''nil))
152          '(function constantly-nil))
153         ((or (eql initform 0)
154              (equal initform ''0))
155          '(function constantly-0))
156         (t
157          (let ((entry (assoc initform *initfunctions-for-this-defclass*
158                              :test #'equal)))
159            (unless entry
160              (setq entry (list initform
161                                (gensym)
162                                `(function (lambda () ,initform))))
163              (push entry *initfunctions-for-this-defclass*))
164            (cadr entry)))))
165
166 (defun canonicalize-slot-specification (class-name spec)
167   (cond ((and (symbolp spec)
168               (not (keywordp spec))
169               (not (memq spec '(t nil))))
170          `'(:name ,spec))
171         ((not (consp spec))
172          (error "~S is not a legal slot specification." spec))
173         ((null (cdr spec))
174          `'(:name ,(car spec)))
175         ((null (cddr spec))
176          (error "In DEFCLASS ~S, the slot specification ~S is obsolete.~%~
177                  Convert it to ~S"
178                 class-name spec (list (car spec) :initform (cadr spec))))
179         (t
180          (let* ((name (pop spec))
181                 (readers ())
182                 (writers ())
183                 (initargs ())
184                 (unsupplied (list nil))
185                 (initform (getf spec :initform unsupplied)))
186            (doplist (key val) spec
187              (case key
188                (:accessor (push val readers)
189                           (push `(setf ,val) writers))
190                (:reader   (push val readers))
191                (:writer   (push val writers))
192                (:initarg  (push val initargs))))
193            (loop (unless (remf spec :accessor) (return)))
194            (loop (unless (remf spec :reader)   (return)))
195            (loop (unless (remf spec :writer)   (return)))
196            (loop (unless (remf spec :initarg)  (return)))
197            (setq *writers-for-this-defclass*
198                  (append writers *writers-for-this-defclass*))
199            (setq *readers-for-this-defclass*
200                  (append readers *readers-for-this-defclass*))
201            (setq spec `(:name     ',name
202                         :readers  ',readers
203                         :writers  ',writers
204                         :initargs ',initargs
205                         ',spec))
206            (if (eq initform unsupplied)
207                `(list* ,@spec)
208                `(list* :initfunction ,(make-initfunction initform) ,@spec))))))
209                                                 
210 (defun canonicalize-defclass-option (class-name option)
211   (declare (ignore class-name))
212   (case (car option)
213     (:default-initargs
214       (let ((canonical ()))
215         (let (key val (tail (cdr option)))
216           (loop (when (null tail) (return nil))
217                 (setq key (pop tail)
218                       val (pop tail))
219                 (push ``(,',key ,,(make-initfunction val) ,',val) canonical))
220           `(:direct-default-initargs (list ,@(nreverse canonical))))))
221     (:documentation
222       `(',(car option) ',(cadr option)))
223     (otherwise
224      `(',(car option) ',(cdr option)))))
225 \f
226 ;;; This is the early definition of LOAD-DEFCLASS. It just collects up
227 ;;; all the class definitions in a list. Later, in braid1.lisp, these
228 ;;; are actually defined.
229
230 ;;; Each entry in *EARLY-CLASS-DEFINITIONS* is an EARLY-CLASS-DEFINITION.
231 (defparameter *early-class-definitions* ())
232
233 (defun early-class-definition (class-name)
234   (or (find class-name *early-class-definitions* :key #'ecd-class-name)
235       (error "~S is not a class in *early-class-definitions*." class-name)))
236
237 (defun make-early-class-definition
238        (name source metaclass
239         superclass-names canonical-slots other-initargs)
240   (list 'early-class-definition
241         name source metaclass
242         superclass-names canonical-slots other-initargs))
243
244 (defun ecd-class-name        (ecd) (nth 1 ecd))
245 (defun ecd-source            (ecd) (nth 2 ecd))
246 (defun ecd-metaclass         (ecd) (nth 3 ecd))
247 (defun ecd-superclass-names  (ecd) (nth 4 ecd))
248 (defun ecd-canonical-slots   (ecd) (nth 5 ecd))
249 (defun ecd-other-initargs    (ecd) (nth 6 ecd))
250
251 (defvar *early-class-slots* nil)
252
253 (defun canonical-slot-name (canonical-slot)
254   (getf canonical-slot :name))
255
256 (defun early-class-slots (class-name)
257   (cdr (or (assoc class-name *early-class-slots*)
258            (let ((a (cons class-name
259                           (mapcar #'canonical-slot-name
260                                   (early-collect-inheritance class-name)))))
261              (push a *early-class-slots*)
262              a))))
263
264 (defun early-class-size (class-name)
265   (length (early-class-slots class-name)))
266
267 (defun early-collect-inheritance (class-name)
268   ;;(declare (values slots cpl default-initargs direct-subclasses))
269   (let ((cpl (early-collect-cpl class-name)))
270     (values (early-collect-slots cpl)
271             cpl
272             (early-collect-default-initargs cpl)
273             (let (collect)
274               (dolist (definition *early-class-definitions*)
275                 (when (memq class-name (ecd-superclass-names definition))
276                   (push (ecd-class-name definition) collect)))
277               (nreverse collect)))))
278
279 (defun early-collect-slots (cpl)
280   (let* ((definitions (mapcar #'early-class-definition cpl))
281          (super-slots (mapcar #'ecd-canonical-slots definitions))
282          (slots (apply #'append (reverse super-slots))))
283     (dolist (s1 slots)
284       (let ((name1 (canonical-slot-name s1)))
285         (dolist (s2 (cdr (memq s1 slots)))
286           (when (eq name1 (canonical-slot-name s2))
287             (error "More than one early class defines a slot with the~%~
288                     name ~S. This can't work because the bootstrap~%~
289                     object system doesn't know how to compute effective~%~
290                     slots."
291                    name1)))))
292     slots))
293
294 (defun early-collect-cpl (class-name)
295   (labels ((walk (c)
296              (let* ((definition (early-class-definition c))
297                     (supers (ecd-superclass-names definition)))
298                (cons c
299                      (apply #'append (mapcar #'early-collect-cpl supers))))))
300     (remove-duplicates (walk class-name) :from-end nil :test #'eq)))
301
302 (defun early-collect-default-initargs (cpl)
303   (let ((default-initargs ()))
304     (dolist (class-name cpl)
305       (let* ((definition (early-class-definition class-name))
306              (others (ecd-other-initargs definition)))
307         (loop (when (null others) (return nil))
308               (let ((initarg (pop others)))
309                 (unless (eq initarg :direct-default-initargs)
310                  (error "~@<The defclass option ~S is not supported by ~
311                         the bootstrap object system.~:@>"
312                         initarg)))
313               (setq default-initargs
314                     (nconc default-initargs (reverse (pop others)))))))
315     (reverse default-initargs)))
316
317 (defun !bootstrap-slot-index (class-name slot-name)
318   (or (position slot-name (early-class-slots class-name))
319       (error "~S not found" slot-name)))
320
321 ;;; !BOOTSTRAP-GET-SLOT and !BOOTSTRAP-SET-SLOT are used to access and
322 ;;; change the values of slots during bootstrapping. During
323 ;;; bootstrapping, there are only two kinds of objects whose slots we
324 ;;; need to access, CLASSes and SLOT-DEFINITIONs. The first argument
325 ;;; to these functions tells whether the object is a CLASS or a
326 ;;; SLOT-DEFINITION.
327 ;;;
328 ;;; Note that the way this works it stores the slot in the same place
329 ;;; in memory that the full object system will expect to find it
330 ;;; later. This is critical to the bootstrapping process, the whole
331 ;;; changeover to the full object system is predicated on this.
332 ;;;
333 ;;; One important point is that the layout of standard classes and
334 ;;; standard slots must be computed the same way in this file as it is
335 ;;; by the full object system later.
336 (defmacro !bootstrap-get-slot (type object slot-name)
337   `(clos-slots-ref (get-slots ,object)
338                    (!bootstrap-slot-index ,type ,slot-name)))
339 (defun !bootstrap-set-slot (type object slot-name new-value)
340   (setf (!bootstrap-get-slot type object slot-name) new-value))
341
342 (defun early-class-name (class)
343   (!bootstrap-get-slot 'class class 'name))
344
345 (defun early-class-precedence-list (class)
346   (!bootstrap-get-slot 'pcl-class class 'class-precedence-list))
347
348 (defun early-class-name-of (instance)
349   (early-class-name (class-of instance)))
350
351 (defun early-class-slotds (class)
352   (!bootstrap-get-slot 'slot-class class 'slots))
353
354 (defun early-slot-definition-name (slotd)
355   (!bootstrap-get-slot 'standard-effective-slot-definition slotd 'name))
356
357 (defun early-slot-definition-location (slotd)
358   (!bootstrap-get-slot 'standard-effective-slot-definition slotd 'location))
359
360 (defun early-accessor-method-slot-name (method)
361   (!bootstrap-get-slot 'standard-accessor-method method 'slot-name))
362
363 (unless (fboundp 'class-name-of)
364   (setf (symbol-function 'class-name-of)
365         (symbol-function 'early-class-name-of)))
366 (unintern 'early-class-name-of)
367
368 (defun early-class-direct-subclasses (class)
369   (!bootstrap-get-slot 'class class 'direct-subclasses))
370
371 (declaim (notinline load-defclass))
372 (defun load-defclass (name metaclass supers canonical-slots canonical-options)
373   (setq supers  (copy-tree supers)
374         canonical-slots   (copy-tree canonical-slots)
375         canonical-options (copy-tree canonical-options))
376   (let ((ecd
377           (make-early-class-definition name
378                                        *load-truename*
379                                        metaclass
380                                        supers
381                                        canonical-slots
382                                        canonical-options))
383         (existing
384           (find name *early-class-definitions* :key #'ecd-class-name)))
385     (setq *early-class-definitions*
386           (cons ecd (remove existing *early-class-definitions*)))
387     ecd))
388