0.9.16.27:
[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 ;;; state for the current DEFCLASS expansion
29 (defvar *initfunctions-for-this-defclass*)
30 (defvar *readers-for-this-defclass*)
31 (defvar *writers-for-this-defclass*)
32 (defvar *slot-names-for-this-defclass*)
33
34 ;;; Like the DEFMETHOD macro, the expansion of the DEFCLASS macro is
35 ;;; fixed. DEFCLASS always expands into a call to LOAD-DEFCLASS. Until
36 ;;; the meta-braid is set up, LOAD-DEFCLASS has a special definition
37 ;;; which simply collects all class definitions up, when the metabraid
38 ;;; is initialized it is done from those class definitions.
39 ;;;
40 ;;; After the metabraid has been setup, and the protocol for defining
41 ;;; classes has been defined, the real definition of LOAD-DEFCLASS is
42 ;;; installed by the file std-class.lisp
43 (defmacro defclass (&environment env name direct-superclasses direct-slots &rest options)
44   (let (*initfunctions-for-this-defclass*
45         *readers-for-this-defclass* ;Truly a crock, but we got
46         *writers-for-this-defclass* ;to have it to live nicely.
47         *slot-names-for-this-defclass*)
48     ;; FIXME: It would be nice to collect all errors from the
49     ;; expansion of a defclass and signal them in a single go.
50     (multiple-value-bind (metaclass canonical-options)
51         (canonize-defclass-options name options)
52     (let ((canonical-slots (canonize-defclass-slots name direct-slots env))
53           ;; DEFSTRUCT-P should be true if the class is defined
54           ;; with a metaclass STRUCTURE-CLASS, so that a DEFSTRUCT
55           ;; is compiled for the class.
56           (defstruct-p (and (eq *boot-state* 'complete)
57                             (let ((mclass (find-class metaclass nil)))
58                               (and mclass
59                                    (*subtypep
60                                     mclass
61                                     *the-class-structure-class*))))))
62       (let* ((defclass-form
63               `(let ,(mapcar #'cdr *initfunctions-for-this-defclass*)
64                  (load-defclass ',name
65                                 ',metaclass
66                                 ',direct-superclasses
67                                 (list ,@canonical-slots)
68                                 (list ,@(apply #'append
69                                                (when defstruct-p
70                                                  '(:from-defclass-p t))
71                                                 canonical-options))
72                                 ',*readers-for-this-defclass*
73                                 ',*writers-for-this-defclass*
74                                 ',*slot-names-for-this-defclass*
75                                 (sb-c:source-location)))))
76         (if defstruct-p
77             (progn
78               ;; FIXME: (YUK!) Why do we do this? Because in order
79               ;; to make the defstruct form, we need to know what
80               ;; the accessors for the slots are, so we need already
81               ;; to have hooked into the CLOS machinery.
82               ;;
83               ;; There may be a better way to do this: it would
84               ;; involve knowing enough about PCL to ask "what will
85               ;; my slot names and accessors be"; failing this, we
86               ;; currently just evaluate the whole kaboodle, and
87               ;; then use CLASS-DIRECT-SLOTS. -- CSR, 2002-06-07
88               (eval defclass-form)
89               (let* ((include (or (and direct-superclasses
90                                        (find-class (car direct-superclasses) nil))
91                                   (and (not (eq name 'structure-object))
92                                        *the-class-structure-object*)))
93                      (defstruct-form (make-structure-class-defstruct-form
94                                       name (class-direct-slots (find-class name))
95                                       include)))
96                 `(progn
97                    (eval-when (:compile-toplevel :load-toplevel :execute)
98                      ,defstruct-form) ; really compile the defstruct-form
99                    (eval-when (:compile-toplevel :load-toplevel :execute)
100                      ,defclass-form))))
101             `(progn
102                ;; By telling the type system at compile time about
103                ;; the existence of a class named NAME, we can avoid
104                ;; various bogus warnings about "type isn't defined yet"
105                ;; for code elsewhere in the same file which uses
106                ;; the name of the type.
107                ;;
108                ;; We only need to do this at compile time, because
109                ;; at load and execute time we write the actual
110                ;; full-blown class, so the "a class of this name is
111                ;; coming" note we write here would be irrelevant.
112                (eval-when (:compile-toplevel)
113                  (%compiler-defclass ',name
114                                      ',*readers-for-this-defclass*
115                                      ',*writers-for-this-defclass*
116                                      ',*slot-names-for-this-defclass*))
117                (eval-when (:load-toplevel :execute)
118                  ,defclass-form))))))))
119
120 (defun canonize-defclass-options (class-name options)
121   (maplist (lambda (sublist)
122              (let ((option-name (first (pop sublist))))
123                (when (member option-name sublist :key #'first)
124                  (error 'simple-program-error
125                         :format-control "Multiple ~S options in DEFCLASS ~S."
126                         :format-arguments (list option-name class-name)))))
127            options)
128   (let (metaclass
129         default-initargs
130         documentation
131         canonized-options)
132       (dolist (option options)
133         (unless (listp option)
134           (error "~S is not a legal defclass option." option))
135         (case (first option)
136           (:metaclass
137            (let ((maybe-metaclass (second option)))
138              (unless (and maybe-metaclass (legal-class-name-p maybe-metaclass))
139                (error 'simple-program-error
140                       :format-control "~@<The value of the :metaclass option (~S) ~
141                          is not a legal class name.~:@>"
142                       :format-arguments (list maybe-metaclass)))
143              (setf metaclass maybe-metaclass)))
144           (:default-initargs
145            (let (initargs arg-names)
146              (doplist (key val) (cdr option)
147                (when (member key arg-names)
148                  (error 'simple-program-error
149                         :format-control "~@<Duplicate initialization argument ~
150                                            name ~S in :DEFAULT-INITARGS of ~
151                                            DEFCLASS ~S.~:>"
152                         :format-arguments (list key class-name)))
153                (push key arg-names)
154                (push ``(,',key ,',val ,,(make-initfunction val)) initargs))
155              (setf default-initargs t)
156              (push `(:direct-default-initargs (list ,@(nreverse initargs)))
157                    canonized-options)))
158           (:documentation
159            (unless (stringp (second option))
160              (error "~S is not a legal :documentation value" (second option)))
161            (setf documentation t)
162            (push `(:documentation ,(second option)) canonized-options))
163           (otherwise
164            (push `(',(car option) ',(cdr option)) canonized-options))))
165       (values (or metaclass 'standard-class) (nreverse canonized-options))))
166
167 (defun canonize-defclass-slots (class-name slots env)
168   (let (canonized-specs)
169     (dolist (spec slots)
170       (when (atom spec)
171         (setf spec (list spec)))
172       (when (and (cdr spec) (null (cddr spec)))
173         (error 'simple-program-error
174                :format-control "~@<in DEFCLASS ~S, the slot specification ~S ~
175                                 is invalid; the probable intended meaning may ~
176                                 be achieved by specifiying ~S instead.~:>"
177                :format-arguments (list class-name spec
178                                        `(,(car spec) :initform ,(cadr spec)))))
179       (let* ((name (car spec))
180              (plist (cdr spec))
181              (readers ())
182              (writers ())
183              (initargs ())
184              (others ())
185              (unsupplied (list nil))
186              (initform unsupplied))
187         (check-slot-name-for-defclass name class-name env)
188         (push name *slot-names-for-this-defclass*)
189         (flet ((note-reader (x)
190                  (unless (symbolp x)
191                    (error 'simple-program-error
192                           :format-control "Slot reader name ~S for slot ~S in ~
193                                            DEFCLASS ~S is not a symbol."
194                           :format-arguments (list x name class-name)))
195                  (push x readers)
196                  (push x *readers-for-this-defclass*))
197                (note-writer (x)
198                  (push x writers)
199                  (push x *writers-for-this-defclass*)))
200           (doplist (key val) plist
201             (case key
202               (:accessor (note-reader val) (note-writer `(setf ,val)))
203               (:reader   (note-reader val))
204               (:writer   (note-writer val))
205               (:initarg
206                (unless (symbolp val)
207                  (error 'simple-program-error
208                         :format-control "Slot initarg name ~S for slot ~S in ~
209                                          DEFCLASS ~S is not a symbol."
210                         :format-arguments (list val name class-name)))
211                (push val initargs))
212               (otherwise
213                (when (member key '(:initform :allocation :type :documentation))
214                  (when (eq key :initform)
215                    (setf initform val))
216                  (when (get-properties others (list key))
217                    (error 'simple-program-error
218                           :format-control "Duplicate slot option ~S for slot ~
219                                            ~S in DEFCLASS ~S."
220                           :format-arguments (list key name class-name))))
221                ;; For non-standard options multiple entries go in a list
222                (push val (getf others key))))))
223         ;; Unwrap singleton lists (AMOP 5.4.2)
224         (do ((head others (cddr head)))
225             ((null head))
226           (unless (cdr (second head))
227             (setf (second head) (car (second head)))))
228         (let ((canon `(:name ',name :readers ',readers :writers ',writers
229                              :initargs ',initargs ',others)))
230           (push (if (eq initform unsupplied)
231                     `(list* ,@canon)
232                     `(list* :initfunction ,(make-initfunction initform)
233                             ,@canon))
234                 canonized-specs))))
235     (nreverse canonized-specs)))
236
237
238 (defun check-slot-name-for-defclass (name class-name env)
239   (flet ((slot-name-illegal (reason)
240            (error 'simple-program-error
241                   :format-control
242                   (format nil "~~@<In DEFCLASS ~~S, the slot name ~~S ~
243                                is ~A.~~@:>" reason)
244                   :format-arguments (list class-name name))))
245     (cond ((not (symbolp name))
246            (slot-name-illegal "not a symbol"))
247           ((keywordp name)
248            (slot-name-illegal "a keyword"))
249           ((constantp name env)
250            (slot-name-illegal "a constant"))
251           ((member name *slot-names-for-this-defclass*)
252            (error 'simple-program-error
253                   :format-control "Multiple slots named ~S in DEFCLASS ~S."
254                   :format-arguments (list name class-name))))))
255
256 (defun make-initfunction (initform)
257   (cond ((or (eq initform t)
258              (equal initform ''t))
259          '(function constantly-t))
260         ((or (eq initform nil)
261              (equal initform ''nil))
262          '(function constantly-nil))
263         ((or (eql initform 0)
264              (equal initform ''0))
265          '(function constantly-0))
266         (t
267          (let ((entry (assoc initform *initfunctions-for-this-defclass*
268                              :test #'equal)))
269            (unless entry
270              (setq entry (list initform
271                                (gensym)
272                                `(function (lambda () ,initform))))
273              (push entry *initfunctions-for-this-defclass*))
274            (cadr entry)))))
275
276 (defun %compiler-defclass (name readers writers slots)
277   ;; ANSI says (Macro DEFCLASS, section 7.7) that DEFCLASS, if it
278   ;; "appears as a top level form, the compiler must make the class
279   ;; name be recognized as a valid type name in subsequent
280   ;; declarations (as for deftype) and be recognized as a valid class
281   ;; name for defmethod parameter specializers and for use as the
282   ;; :metaclass option of a subsequent defclass."
283   (preinform-compiler-about-class-type name)
284   (preinform-compiler-about-accessors readers writers slots))
285
286 (defun preinform-compiler-about-class-type (name)
287   ;; Unless the type system already has an actual type attached to
288   ;; NAME (in which case (1) writing a placeholder value over that
289   ;; actual type as a compile-time side-effect would probably be a bad
290   ;; idea and (2) anyway we don't need to modify it in order to make
291   ;; NAME be recognized as a valid type name)
292   (unless (info :type :kind name)
293     ;; Tell the compiler to expect a class with the given NAME, by
294     ;; writing a kind of minimal placeholder type information. This
295     ;; placeholder will be overwritten later when the class is defined.
296     (setf (info :type :kind name) :forthcoming-defclass-type))
297   (values))
298
299 (defun preinform-compiler-about-accessors (readers writers slots)
300   (flet ((inform (name type)
301            ;; FIXME: This matches what PROCLAIM FTYPE does, except
302            ;; that :WHERE-FROM is :DEFINED, not :DECLARED, and should
303            ;; probably be factored into a common function -- eg.
304            ;; (%proclaim-ftype name declared-or-defined).
305            (when (eq (info :function :where-from name) :assumed)
306              (proclaim-as-fun-name name)
307              (note-name-defined name :function)
308              (setf (info :function :where-from name) :defined
309                    (info :function :type name) type))))
310     (let ((rtype (specifier-type '(function (t) t)))
311           (wtype (specifier-type '(function (t t) t))))
312       (dolist (reader readers)
313         (inform reader rtype))
314       (dolist (writer writers)
315         (inform writer wtype))
316       (dolist (slot slots)
317         (inform (slot-reader-name slot) rtype)
318         (inform (slot-boundp-name slot) rtype)
319         (inform (slot-writer-name slot) wtype)))))
320 \f
321 ;;; This is the early definition of LOAD-DEFCLASS. It just collects up
322 ;;; all the class definitions in a list. Later, in braid1.lisp, these
323 ;;; are actually defined.
324
325 ;;; Each entry in *EARLY-CLASS-DEFINITIONS* is an EARLY-CLASS-DEFINITION.
326 (defparameter *early-class-definitions* ())
327
328 (defun early-class-definition (class-name)
329   (or (find class-name *early-class-definitions* :key #'ecd-class-name)
330       (error "~S is not a class in *early-class-definitions*." class-name)))
331
332 (defun make-early-class-definition
333        (name source-location metaclass
334         superclass-names canonical-slots other-initargs)
335   (list 'early-class-definition
336         name source-location metaclass
337         superclass-names canonical-slots other-initargs))
338
339 (defun ecd-class-name        (ecd) (nth 1 ecd))
340 (defun ecd-source-location   (ecd) (nth 2 ecd))
341 (defun ecd-metaclass         (ecd) (nth 3 ecd))
342 (defun ecd-superclass-names  (ecd) (nth 4 ecd))
343 (defun ecd-canonical-slots   (ecd) (nth 5 ecd))
344 (defun ecd-other-initargs    (ecd) (nth 6 ecd))
345
346 (defvar *early-class-slots* nil)
347
348 (defun canonical-slot-name (canonical-slot)
349   (getf canonical-slot :name))
350
351 (defun early-class-slots (class-name)
352   (cdr (or (assoc class-name *early-class-slots*)
353            (let ((a (cons class-name
354                           (mapcar #'canonical-slot-name
355                                   (early-collect-inheritance class-name)))))
356              (push a *early-class-slots*)
357              a))))
358
359 (defun early-class-size (class-name)
360   (length (early-class-slots class-name)))
361
362 (defun early-collect-inheritance (class-name)
363   ;;(declare (values slots cpl default-initargs direct-subclasses))
364   (let ((cpl (early-collect-cpl class-name)))
365     (values (early-collect-slots cpl)
366             cpl
367             (early-collect-default-initargs cpl)
368             (let (collect)
369               (dolist (definition *early-class-definitions*)
370                 (when (memq class-name (ecd-superclass-names definition))
371                   (push (ecd-class-name definition) collect)))
372               (nreverse collect)))))
373
374 (defun early-collect-slots (cpl)
375   (let* ((definitions (mapcar #'early-class-definition cpl))
376          (super-slots (mapcar #'ecd-canonical-slots definitions))
377          (slots (apply #'append (reverse super-slots))))
378     (dolist (s1 slots)
379       (let ((name1 (canonical-slot-name s1)))
380         (dolist (s2 (cdr (memq s1 slots)))
381           (when (eq name1 (canonical-slot-name s2))
382             (error "More than one early class defines a slot with the~%~
383                     name ~S. This can't work because the bootstrap~%~
384                     object system doesn't know how to compute effective~%~
385                     slots."
386                    name1)))))
387     slots))
388
389 (defun early-collect-cpl (class-name)
390   (labels ((walk (c)
391              (let* ((definition (early-class-definition c))
392                     (supers (ecd-superclass-names definition)))
393                (cons c
394                      (apply #'append (mapcar #'early-collect-cpl supers))))))
395     (remove-duplicates (walk class-name) :from-end nil :test #'eq)))
396
397 (defun early-collect-default-initargs (cpl)
398   (let ((default-initargs ()))
399     (dolist (class-name cpl)
400       (let* ((definition (early-class-definition class-name))
401              (others (ecd-other-initargs definition)))
402         (loop (when (null others) (return nil))
403               (let ((initarg (pop others)))
404                 (unless (eq initarg :direct-default-initargs)
405                  (error "~@<The defclass option ~S is not supported by ~
406                         the bootstrap object system.~:@>"
407                         initarg)))
408               (setq default-initargs
409                     (nconc default-initargs (reverse (pop others)))))))
410     (reverse default-initargs)))
411
412 (defun !bootstrap-slot-index (class-name slot-name)
413   (or (position slot-name (early-class-slots class-name))
414       (error "~S not found" slot-name)))
415
416 ;;; !BOOTSTRAP-GET-SLOT and !BOOTSTRAP-SET-SLOT are used to access and
417 ;;; change the values of slots during bootstrapping. During
418 ;;; bootstrapping, there are only two kinds of objects whose slots we
419 ;;; need to access, CLASSes and SLOT-DEFINITIONs. The first argument
420 ;;; to these functions tells whether the object is a CLASS or a
421 ;;; SLOT-DEFINITION.
422 ;;;
423 ;;; Note that the way this works it stores the slot in the same place
424 ;;; in memory that the full object system will expect to find it
425 ;;; later. This is critical to the bootstrapping process, the whole
426 ;;; changeover to the full object system is predicated on this.
427 ;;;
428 ;;; One important point is that the layout of standard classes and
429 ;;; standard slots must be computed the same way in this file as it is
430 ;;; by the full object system later.
431 (defmacro !bootstrap-get-slot (type object slot-name)
432   `(clos-slots-ref (get-slots ,object)
433                    (!bootstrap-slot-index ,type ,slot-name)))
434 (defun !bootstrap-set-slot (type object slot-name new-value)
435   (setf (!bootstrap-get-slot type object slot-name) new-value))
436
437 (defun early-class-name (class)
438   (!bootstrap-get-slot 'class class 'name))
439
440 (defun early-class-precedence-list (class)
441   (!bootstrap-get-slot 'pcl-class class '%class-precedence-list))
442
443 (defun early-class-name-of (instance)
444   (early-class-name (class-of instance)))
445
446 (defun early-class-slotds (class)
447   (!bootstrap-get-slot 'slot-class class 'slots))
448
449 (defun early-slot-definition-name (slotd)
450   (!bootstrap-get-slot 'standard-effective-slot-definition slotd 'name))
451
452 (defun early-slot-definition-location (slotd)
453   (!bootstrap-get-slot 'standard-effective-slot-definition slotd 'location))
454
455 (defun early-accessor-method-slot-name (method)
456   (!bootstrap-get-slot 'standard-accessor-method method 'slot-name))
457
458 (unless (fboundp 'class-name-of)
459   (setf (symbol-function 'class-name-of)
460         (symbol-function 'early-class-name-of)))
461 (unintern 'early-class-name-of)
462
463 (defun early-class-direct-subclasses (class)
464   (!bootstrap-get-slot 'class class 'direct-subclasses))
465
466 (declaim (notinline load-defclass))
467 (defun load-defclass (name metaclass supers canonical-slots canonical-options
468                       readers writers slot-names source-location)
469   (%compiler-defclass name readers writers slot-names)
470   (setq supers  (copy-tree supers)
471         canonical-slots   (copy-tree canonical-slots)
472         canonical-options (copy-tree canonical-options))
473   (let ((ecd
474           (make-early-class-definition name
475                                        source-location
476                                        metaclass
477                                        supers
478                                        canonical-slots
479                                        canonical-options))
480         (existing
481           (find name *early-class-definitions* :key #'ecd-class-name)))
482     (setq *early-class-definitions*
483           (cons ecd (remove existing *early-class-definitions*)))
484     ecd))