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