2d1476b2f17beb95da52c04f6ef92e5e20aaf92b
[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 ;;; MAKE-TOP-LEVEL-FORM is used by all PCL macros that appear `at top-level'.
27 ;;;
28 ;;; The original motiviation for this function was to deal with the
29 ;;; bug in the Genera compiler that prevents lambda expressions in
30 ;;; top-level forms other than DEFUN from being compiled.
31 ;;;
32 ;;; Now this function is used to grab other functionality as well. This
33 ;;; includes:
34 ;;;   - Preventing the grouping of top-level forms. For example, a
35 ;;;     DEFCLASS followed by a DEFMETHOD may not want to be grouped
36 ;;;     into the same top-level form.
37 ;;;   - Telling the programming environment what the pretty version
38 ;;;     of the name of this form is. This is used by WARN.
39 ;;;
40 ;;; FIXME: It's not clear that this adds value any more. Couldn't
41 ;;; we just use EVAL-WHEN?
42 (defun make-top-level-form (name times form)
43   (if (or (member 'compile times)
44           (member ':compile-toplevel times))
45       `(eval-when ,times ,form)
46       form))
47
48 (defun make-progn (&rest forms)
49   (let ((progn-form nil))
50     (labels ((collect-forms (forms)
51                (unless (null forms)
52                  (collect-forms (cdr forms))
53                  (if (and (listp (car forms))
54                           (eq (caar forms) 'progn))
55                      (collect-forms (cdar forms))
56                      (push (car forms) progn-form)))))
57       (collect-forms forms)
58       (cons 'progn progn-form))))
59 \f
60 ;;; Like the DEFMETHOD macro, the expansion of the DEFCLASS macro is
61 ;;; fixed. DEFCLASS always expands into a call to LOAD-DEFCLASS. Until
62 ;;; the meta-braid is set up, LOAD-DEFCLASS has a special definition
63 ;;; which simply collects all class definitions up, when the metabraid
64 ;;; is initialized it is done from those class definitions.
65 ;;;
66 ;;; After the metabraid has been setup, and the protocol for defining
67 ;;; classes has been defined, the real definition of LOAD-DEFCLASS is
68 ;;; installed by the file defclass.lisp
69 (defmacro defclass (name direct-superclasses direct-slots &rest options)
70   (expand-defclass name direct-superclasses direct-slots options))
71
72 (defun expand-defclass (name supers slots options)
73   ;; FIXME: We should probably just ensure that the relevant
74   ;; DEFVAR/DEFPARAMETERs occur before this definition, rather 
75   ;; than locally declaring them SPECIAL.
76   (declare (special *defclass-times* *boot-state* *the-class-structure-class*))
77   (setq supers  (copy-tree supers)
78         slots   (copy-tree slots)
79         options (copy-tree options))
80   (let ((metaclass 'standard-class))
81     (dolist (option options)
82       (if (not (listp option))
83           (error "~S is not a legal defclass option." option)
84           (when (eq (car option) ':metaclass)
85             (unless (legal-class-name-p (cadr option))
86               (error "The value of the :metaclass option (~S) is not a~%~
87                       legal class name."
88                      (cadr option)))
89             (setq metaclass
90                   (case (cadr option)
91                     (cl:standard-class 'standard-class)
92                     (cl:structure-class 'structure-class)
93                     (t (cadr option))))
94             (setf options (remove option options))
95             (return t))))
96
97     (let ((*initfunctions* ())
98           (*accessors* ())              ;Truly a crock, but we got
99           (*readers* ())                ;to have it to live nicely.
100           (*writers* ()))
101       (declare (special *initfunctions* *accessors* *readers* *writers*))
102       (let ((canonical-slots
103               (mapcar #'(lambda (spec)
104                           (canonicalize-slot-specification name spec))
105                       slots))
106             (other-initargs
107               (mapcar #'(lambda (option)
108                           (canonicalize-defclass-option name option))
109                       options))
110             (defstruct-p (and (eq *boot-state* 'complete)
111                               (let ((mclass (find-class metaclass nil)))
112                                 (and mclass
113                                      (*subtypep mclass
114                                                 *the-class-structure-class*))))))
115         (do-standard-defsetfs-for-defclass *accessors*)
116         (let ((defclass-form
117                  (make-top-level-form `(defclass ,name)
118                    (if defstruct-p '(:load-toplevel :execute) *defclass-times*)
119                    `(progn
120                       ,@(mapcar #'(lambda (x)
121                                     `(declaim (ftype (function (t) t) ,x)))
122                                 *readers*)
123                       ,@(mapcar #'(lambda (x)
124                                     #-setf (when (consp x)
125                                              (setq x (get-setf-function-name (cadr x))))
126                                     `(declaim (ftype (function (t t) t) ,x)))
127                                 *writers*)
128                       (let ,(mapcar #'cdr *initfunctions*)
129                         (load-defclass ',name
130                                        ',metaclass
131                                        ',supers
132                                        (list ,@canonical-slots)
133                                        (list ,@(apply #'append
134                                                       (when defstruct-p
135                                                         '(:from-defclass-p t))
136                                                       other-initargs))
137                                        ',*accessors*))))))
138           (if defstruct-p
139               (progn
140                 (eval defclass-form) ; Define the class now, so that..
141                 `(progn       ; ..the defstruct can be compiled.
142                    ,(class-defstruct-form (find-class name))
143                    ,defclass-form))
144               (progn
145                 (when (and (eq *boot-state* 'complete)
146                            (not (member 'compile *defclass-times*)))
147                   (inform-type-system-about-std-class name))
148                 defclass-form)))))))
149
150 (defun make-initfunction (initform)
151   (declare (special *initfunctions*))
152   (cond ((or (eq initform 't)
153              (equal initform ''t))
154          '(function constantly-t))
155         ((or (eq initform 'nil)
156              (equal initform ''nil))
157          '(function constantly-nil))
158         ((or (eql initform '0)
159              (equal initform ''0))
160          '(function constantly-0))
161         (t
162          (let ((entry (assoc initform *initfunctions* :test #'equal)))
163            (unless entry
164              (setq entry (list initform
165                                (gensym)
166                                `(function (lambda () ,initform))))
167              (push entry *initfunctions*))
168            (cadr entry)))))
169
170 (defun canonicalize-slot-specification (class-name spec)
171   (declare (special *accessors* *readers* *writers*))
172   (cond ((and (symbolp spec)
173               (not (keywordp spec))
174               (not (memq spec '(t nil))))
175          `'(:name ,spec))
176         ((not (consp spec))
177          (error "~S is not a legal slot specification." spec))
178         ((null (cdr spec))
179          `'(:name ,(car spec)))
180         ((null (cddr spec))
181          (error "In DEFCLASS ~S, the slot specification ~S is obsolete.~%~
182                  Convert it to ~S"
183                 class-name spec (list (car spec) :initform (cadr spec))))
184         (t
185          (let* ((name (pop spec))
186                 (readers ())
187                 (writers ())
188                 (initargs ())
189                 (unsupplied (list nil))
190                 (initform (getf spec :initform unsupplied)))
191            (doplist (key val) spec
192              (case key
193                (:accessor (push val *accessors*)
194                           (push val readers)
195                           (push `(setf ,val) writers))
196                (:reader   (push val readers))
197                (:writer   (push val writers))
198                (:initarg  (push val initargs))))
199            (loop (unless (remf spec :accessor) (return)))
200            (loop (unless (remf spec :reader)   (return)))
201            (loop (unless (remf spec :writer)   (return)))
202            (loop (unless (remf spec :initarg)  (return)))
203            (setq *writers* (append writers *writers*))
204            (setq *readers* (append readers *readers*))
205            (setq spec `(:name     ',name
206                         :readers  ',readers
207                         :writers  ',writers
208                         :initargs ',initargs
209                         ',spec))
210            (if (eq initform unsupplied)
211                `(list* ,@spec)
212                `(list* :initfunction ,(make-initfunction initform) ,@spec))))))
213                                                 
214 (defun canonicalize-defclass-option (class-name option)
215   (declare (ignore class-name))
216   (case (car option)
217     (:default-initargs
218       (let ((canonical ()))
219         (let (key val (tail (cdr option)))
220           (loop (when (null tail) (return nil))
221                 (setq key (pop tail)
222                       val (pop tail))
223                 (push ``(,',key ,,(make-initfunction val) ,',val) canonical))
224           `(':direct-default-initargs (list ,@(nreverse canonical))))))
225     (:documentation
226       `(',(car option) ',(cadr option)))
227     (otherwise
228      `(',(car option) ',(cdr option)))))
229 \f
230 ;;; This is the early definition of load-defclass. It just collects up
231 ;;; all the class definitions in a list. Later, in the file
232 ;;; braid1.lisp, these are actually defined.
233
234 ;;; Each entry in *EARLY-CLASS-DEFINITIONS* is an EARLY-CLASS-DEFINITION.
235 (defparameter *early-class-definitions* ())
236
237 (defun early-class-definition (class-name)
238   (or (find class-name *early-class-definitions* :key #'ecd-class-name)
239       (error "~S is not a class in *early-class-definitions*." class-name)))
240
241 (defun make-early-class-definition
242        (name source metaclass
243         superclass-names canonical-slots other-initargs)
244   (list 'early-class-definition
245         name source metaclass
246         superclass-names canonical-slots other-initargs))
247
248 (defun ecd-class-name        (ecd) (nth 1 ecd))
249 (defun ecd-source            (ecd) (nth 2 ecd))
250 (defun ecd-metaclass         (ecd) (nth 3 ecd))
251 (defun ecd-superclass-names  (ecd) (nth 4 ecd))
252 (defun ecd-canonical-slots   (ecd) (nth 5 ecd))
253 (defun ecd-other-initargs    (ecd) (nth 6 ecd))
254
255 (defvar *early-class-slots* nil)
256
257 (defun canonical-slot-name (canonical-slot)
258   (getf canonical-slot :name))
259
260 (defun early-class-slots (class-name)
261   (cdr (or (assoc class-name *early-class-slots*)
262            (let ((a (cons class-name
263                           (mapcar #'canonical-slot-name
264                                   (early-collect-inheritance class-name)))))
265              (push a *early-class-slots*)
266              a))))
267
268 (defun early-class-size (class-name)
269   (length (early-class-slots class-name)))
270
271 (defun early-collect-inheritance (class-name)
272   ;;(declare (values slots cpl default-initargs direct-subclasses))
273   (let ((cpl (early-collect-cpl class-name)))
274     (values (early-collect-slots cpl)
275             cpl
276             (early-collect-default-initargs cpl)
277             (gathering1 (collecting)
278               (dolist (definition *early-class-definitions*)
279                 (when (memq class-name (ecd-superclass-names definition))
280                   (gather1 (ecd-class-name definition))))))))
281
282 (defun early-collect-slots (cpl)
283   (let* ((definitions (mapcar #'early-class-definition cpl))
284          (super-slots (mapcar #'ecd-canonical-slots definitions))
285          (slots (apply #'append (reverse super-slots))))
286     (dolist (s1 slots)
287       (let ((name1 (canonical-slot-name s1)))
288         (dolist (s2 (cdr (memq s1 slots)))
289           (when (eq name1 (canonical-slot-name s2))
290             (error "More than one early class defines a slot with the~%~
291                     name ~S. This can't work because the bootstrap~%~
292                     object system doesn't know how to compute effective~%~
293                     slots."
294                    name1)))))
295     slots))
296
297 (defun early-collect-cpl (class-name)
298   (labels ((walk (c)
299              (let* ((definition (early-class-definition c))
300                     (supers (ecd-superclass-names definition)))
301                (cons c
302                      (apply #'append (mapcar #'early-collect-cpl supers))))))
303     (remove-duplicates (walk class-name) :from-end nil :test #'eq)))
304
305 (defun early-collect-default-initargs (cpl)
306   (let ((default-initargs ()))
307     (dolist (class-name cpl)
308       (let* ((definition (early-class-definition class-name))
309              (others (ecd-other-initargs definition)))
310         (loop (when (null others) (return nil))
311               (let ((initarg (pop others)))
312                 (unless (eq initarg :direct-default-initargs)
313                  (error "The defclass option ~S is not supported by the bootstrap~%~
314                         object system."
315                         initarg)))
316               (setq default-initargs
317                     (nconc default-initargs (reverse (pop others)))))))
318     (reverse default-initargs)))
319
320 (defun !bootstrap-slot-index (class-name slot-name)
321   (or (position slot-name (early-class-slots class-name))
322       (error "~S not found" slot-name)))
323
324 ;;; !BOOTSTRAP-GET-SLOT and !BOOTSTRAP-SET-SLOT are used to access and
325 ;;; change the values of slots during bootstrapping. During
326 ;;; bootstrapping, there are only two kinds of objects whose slots we
327 ;;; need to access, CLASSes and SLOT-DEFINITIONs. The first argument
328 ;;; to these functions tells whether the object is a CLASS or a
329 ;;; SLOT-DEFINITION.
330 ;;;
331 ;;; Note that the way this works it stores the slot in the same place
332 ;;; in memory that the full object system will expect to find it
333 ;;; later. This is critical to the bootstrapping process, the whole
334 ;;; changeover to the full object system is predicated on this.
335 ;;;
336 ;;; One important point is that the layout of standard classes and
337 ;;; standard slots must be computed the same way in this file as it is
338 ;;; by the full object system later.
339 (defmacro !bootstrap-get-slot (type object slot-name)
340   `(instance-ref (get-slots ,object) (!bootstrap-slot-index ,type ,slot-name)))
341 (defun !bootstrap-set-slot (type object slot-name new-value)
342   (setf (!bootstrap-get-slot type object slot-name) new-value))
343
344 (defun early-class-name (class)
345   (!bootstrap-get-slot 'class class 'name))
346
347 (defun early-class-precedence-list (class)
348   (!bootstrap-get-slot 'pcl-class class 'class-precedence-list))
349
350 (defun early-class-name-of (instance)
351   (early-class-name (class-of instance)))
352
353 (defun early-class-slotds (class)
354   (!bootstrap-get-slot 'slot-class class 'slots))
355
356 (defun early-slot-definition-name (slotd)
357   (!bootstrap-get-slot 'standard-effective-slot-definition slotd 'name))
358
359 (defun early-slot-definition-location (slotd)
360   (!bootstrap-get-slot 'standard-effective-slot-definition slotd 'location))
361
362 (defun early-accessor-method-slot-name (method)
363   (!bootstrap-get-slot 'standard-accessor-method method 'slot-name))
364
365 (unless (fboundp 'class-name-of)
366   (setf (symbol-function 'class-name-of)
367         (symbol-function 'early-class-name-of)))
368 ;;; FIXME: Can we then delete EARLY-CLASS-NAME-OF?
369
370 (defun early-class-direct-subclasses (class)
371   (!bootstrap-get-slot 'class class 'direct-subclasses))
372
373 (declaim (notinline load-defclass))
374 (defun load-defclass
375        (name metaclass supers canonical-slots canonical-options accessor-names)
376   (setq supers  (copy-tree supers)
377         canonical-slots   (copy-tree canonical-slots)
378         canonical-options (copy-tree canonical-options))
379   (do-standard-defsetfs-for-defclass accessor-names)
380   (when (eq metaclass 'standard-class)
381     (inform-type-system-about-std-class name))
382   (let ((ecd
383           (make-early-class-definition name
384                                        *load-truename*
385                                        metaclass
386                                        supers
387                                        canonical-slots
388                                        canonical-options))
389         (existing
390           (find name *early-class-definitions* :key #'ecd-class-name)))
391     (setq *early-class-definitions*
392           (cons ecd (remove existing *early-class-definitions*)))
393     ecd))
394