ead055ed4a0c185cfe9128ad627bd28f7c33fe42
[sbcl.git] / src / code / defbangstruct.lisp
1 ;;;; DEF!STRUCT = bootstrap DEFSTRUCT, a wrapper around DEFSTRUCT which
2 ;;;; provides special features to help at bootstrap time:
3 ;;;;  1. Layout information, inheritance information, and so forth is
4 ;;;;     retained in such a way that we can get to it even on vanilla
5 ;;;;     ANSI Common Lisp at cross-compiler build time.
6 ;;;;  2. MAKE-LOAD-FORM information is stored in such a way that we can
7 ;;;;     get to it at bootstrap time before CLOS is built. This is
8 ;;;;     important because at least as of sbcl-0.6.11.26, CLOS is built
9 ;;;;     (compiled) after cold init, so we need to have the compiler
10 ;;;;     even before CLOS runs.
11
12 ;;;; This software is part of the SBCL system. See the README file for
13 ;;;; more information.
14 ;;;;
15 ;;;; This software is derived from the CMU CL system, which was
16 ;;;; written at Carnegie Mellon University and released into the
17 ;;;; public domain. The software is in the public domain and is
18 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
19 ;;;; files for more information.
20
21 (in-package "SB!KERNEL")
22
23 ;;; A bootstrap MAKE-LOAD-FORM method can be a function or the name
24 ;;; of a function.
25 (deftype def!struct-type-make-load-form-fun () '(or function symbol))
26
27 ;;; a little single-inheritance system to keep track of MAKE-LOAD-FORM
28 ;;; information for DEF!STRUCT-defined types
29 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
30
31   ;; FIXME: All this could be byte compiled. (Perhaps most of the rest
32   ;; of the file could be, too.)
33
34   ;; (DEF!STRUCT-SUPERTYPE TYPE) is the DEF!STRUCT-defined type that
35   ;; TYPE inherits from, or NIL if none.
36   (defvar *def!struct-supertype* (make-hash-table))
37   (defun def!struct-supertype (type)
38     (multiple-value-bind (value value-p) (gethash type *def!struct-supertype*)
39       (unless value-p
40         (error "~S is not a DEF!STRUCT-defined type." type))
41       value))
42   (defun (setf def!struct-supertype) (value type)
43     (when (and value #-sb-xc-host *type-system-initialized*)
44       (aver (subtypep value 'structure!object))
45       (aver (subtypep type value)))
46     (setf (gethash type *def!struct-supertype*) value))
47
48   ;; (DEF!STRUCT-TYPE-MAKE-LOAD-FORM-FUN TYPE) is the load form
49   ;; generator associated with the DEF!STRUCT-defined structure named
50   ;; TYPE, stored in a way which works independently of CLOS. The
51   ;; *DEF!STRUCT-TYPE-MAKE-LOAD-FORM-FUN* table is used to store the
52   ;; values. All types defined by DEF!STRUCT have an entry in the
53   ;; table; those with no MAKE-LOAD-FORM function have an explicit NIL
54   ;; entry.
55   (defvar *def!struct-type-make-load-form-fun* (make-hash-table))
56   (defun def!struct-type-make-load-form-fun (type)
57     (do ((supertype type))
58         (nil)
59       (multiple-value-bind (value value-p)
60           (gethash supertype *def!struct-type-make-load-form-fun*)
61         (unless value-p
62           (error "~S (supertype of ~S) is not a DEF!STRUCT-defined type."
63                  supertype
64                  type))
65         (when value
66           (return value))
67         (setf supertype (def!struct-supertype supertype))
68         (unless supertype
69           (error "There is no MAKE-LOAD-FORM function for bootstrap type ~S."
70                  type)))))
71   (defun (setf def!struct-type-make-load-form-fun) (new-value type)
72     (when #+sb-xc-host t #-sb-xc-host *type-system-initialized*
73       (aver (subtypep type 'structure!object))
74       (aver (typep new-value 'def!struct-type-make-load-form-fun)))
75     (setf (gethash type *def!struct-type-make-load-form-fun*) new-value)))
76
77 ;;; the simplest, most vanilla MAKE-LOAD-FORM function for DEF!STRUCT
78 ;;; objects
79 (defun just-dump-it-normally (object &optional (env nil env-p))
80   (declare (type structure!object object))
81   (if env-p
82       (make-load-form-saving-slots object :environment env)
83       (make-load-form-saving-slots object)))
84
85 ;;; a MAKE-LOAD-FORM function for objects which don't use the load
86 ;;; form system. This is used for LAYOUT objects because the special
87 ;;; dumping requirements of LAYOUT objects are met by using special
88 ;;; VOPs which bypass the load form system. It's also used for various
89 ;;; compiler internal structures like nodes and VOP-INFO (FIXME:
90 ;;; Why?).
91 (defun ignore-it (object &optional env)
92   (declare (type structure!object object))
93   (declare (ignore object env))
94   ;; This magic tag is handled specially by the compiler downstream.
95   :ignore-it)
96
97 ;;; machinery used in the implementation of DEF!STRUCT
98 #+sb-xc-host
99 (eval-when (:compile-toplevel :load-toplevel :execute)
100   ;; a description of a DEF!STRUCT call to be stored until we get
101   ;; enough of the system running to finish processing it
102   (defstruct delayed-def!struct
103     (args (required-argument) :type cons)
104     (package (sane-package) :type package))
105   ;; a list of DELAYED-DEF!STRUCTs stored until we get DEF!STRUCT
106   ;; working fully so that we can apply it to them then. After
107   ;; DEF!STRUCT is made to work fully, this list is processed, then
108   ;; made unbound, and should no longer be used.
109   (defvar *delayed-def!structs* nil))
110 (eval-when (:compile-toplevel :load-toplevel :execute)
111   ;; Parse the arguments for a DEF!STRUCT call, and return
112   ;;   (VALUES NAME DEFSTRUCT-ARGS MAKE-LOAD-FORM-FUN DEF!STRUCT-SUPERTYPE),
113   ;; where NAME is the name of the new type, DEFSTRUCT-ARGS is the
114   ;; munged result suitable for passing on to DEFSTRUCT,
115   ;; MAKE-LOAD-FORM-FUN is the make load form function, or NIL if
116   ;; there's none, and DEF!STRUCT-SUPERTYPE is the direct supertype of
117   ;; the type if it is another DEF!STRUCT-defined type, or NIL
118   ;; otherwise.
119   (defun parse-def!struct-args (nameoid &rest rest)
120     (multiple-value-bind (name options) ; Note: OPTIONS can change below.
121         (if (consp nameoid)
122             (values (first nameoid) (rest nameoid))
123             (values nameoid nil))
124       (let* ((include-clause (find :include options :key #'first))
125              (def!struct-supertype nil) ; may change below
126              (mlff-clause (find :make-load-form-fun options :key #'first))
127              (mlff (and mlff-clause (second mlff-clause))))
128         (when (find :type options :key #'first)
129           (error "can't use :TYPE option in DEF!STRUCT"))
130         (when mlff-clause
131           (setf options (remove mlff-clause options)))
132         (when include-clause
133           (setf def!struct-supertype (second include-clause)))
134         (if (eq name 'structure!object) ; if root of hierarchy
135             (aver (not include-clause))
136             (unless include-clause
137               (setf def!struct-supertype 'structure!object)
138               (push `(:include ,def!struct-supertype) options)))
139         (values name `((,name ,@options) ,@rest) mlff def!struct-supertype)))))
140
141 ;;; Part of the raison d'etre for DEF!STRUCT is to be able to emulate
142 ;;; these low-level CMU CL functions in a vanilla ANSI Common Lisp
143 ;;; cross compilation host. (The emulation doesn't need to be
144 ;;; efficient, since it's needed for things like dumping objects, not
145 ;;; inner loops.)
146 #+sb-xc-host
147 (progn
148   (defun %instance-length (instance)
149     (aver (typep instance 'structure!object))
150     (layout-length (class-layout (sb!xc:find-class (type-of instance)))))
151   (defun %instance-ref (instance index)
152     (aver (typep instance 'structure!object))
153     (let* ((class (sb!xc:find-class (type-of instance)))
154            (layout (class-layout class)))
155       (if (zerop index)
156           layout
157           (let* ((dd (layout-info layout))
158                  (dsd (elt (dd-slots dd) (1- index)))
159                  (accessor-name (dsd-accessor-name dsd)))
160             (declare (type symbol accessor-name))
161             (funcall accessor-name instance)))))
162   (defun %instance-set (instance index new-value)
163     (aver (typep instance 'structure!object))
164     (let* ((class (sb!xc:find-class (type-of instance)))
165            (layout (class-layout class)))
166       (if (zerop index)
167           (error "can't set %INSTANCE-REF FOO 0 in cross-compilation host")
168           (let* ((dd (layout-info layout))
169                  (dsd (elt (dd-slots dd) (1- index)))
170                  (accessor-name (dsd-accessor-name dsd)))
171             (declare (type symbol accessor-name))
172             (funcall (fdefinition `(setf ,accessor-name))
173                      new-value
174                      instance))))))
175
176 ;;; a helper function for DEF!STRUCT in the #+SB-XC-HOST case: Return
177 ;;; DEFSTRUCT-style arguments with any class names in the SB!XC
178 ;;; package (i.e. the name of the class being defined, and/or the
179 ;;; names of classes in :INCLUDE clauses) converted from SB!XC::FOO to
180 ;;; CL::FOO.
181 #+sb-xc-host
182 (eval-when (:compile-toplevel :load-toplevel :execute)
183   (defun uncross-defstruct-args (defstruct-args)
184     (destructuring-bind (name-and-options &rest slots-and-doc) defstruct-args
185       (multiple-value-bind (name options)
186           (if (symbolp name-and-options)
187               (values name-and-options nil)
188               (values (first name-and-options)
189                       (rest name-and-options)))
190         (flet ((uncross-option (option)
191                  (if (eq (first option) :include)
192                      (destructuring-bind
193                          (include-keyword included-name &rest rest)
194                          option
195                        `(,include-keyword
196                          ,(uncross included-name)
197                          ,@rest))
198                    option)))
199           `((,(uncross name)
200              ,@(mapcar #'uncross-option options))
201             ,@slots-and-doc))))))
202
203 ;;; DEF!STRUCT's arguments are like DEFSTRUCT's arguments, except that
204 ;;; DEF!STRUCT accepts an extra optional :MAKE-LOAD-FORM-FUN clause.
205 ;;; DEF!STRUCT also does some magic to ensure that anything it defines
206 ;;; includes STRUCTURE!OBJECT, so that when CLOS is/becomes available,
207 ;;; we can hook the DEF!STRUCT system into
208 ;;;   (DEFMETHOD MAKE-LOAD-FORM ((X STRUCTURE!OBJECT) &OPTIONAL ENV) ..)
209 ;;; and everything will continue to work.
210 (defmacro def!struct (&rest args)
211   (multiple-value-bind (name defstruct-args mlff def!struct-supertype)
212       (apply #'parse-def!struct-args args)
213     `(progn
214        ;; Make sure that we really do include STRUCTURE!OBJECT. (If an
215        ;; :INCLUDE clause was used, and the included class didn't
216        ;; itself include STRUCTURE!OBJECT, then we wouldn't; and it's
217        ;; better to find out ASAP then to let the bug lurk until
218        ;; someone tries to do MAKE-LOAD-FORM on the object.)
219        (aver (subtypep ',def!struct-supertype 'structure!object))
220        (defstruct ,@defstruct-args)
221        (setf (def!struct-type-make-load-form-fun ',name)
222              ,(if (symbolp mlff)
223                   `',mlff
224                   mlff)
225              (def!struct-supertype ',name)
226              ',def!struct-supertype)
227        ;; This bit of commented-out code hasn't been needed for quite
228        ;; some time, but the comments here about why not might still
229        ;; be useful to me until I finally get the system to work. When
230        ;; I do remove all this, I should be sure also to remove the
231        ;; "outside the EVAL-WHEN" comments above, since they will no
232        ;; longer make sense. -- WHN 19990803
233        ;;(eval-when (:compile-toplevel :load-toplevel :execute)
234        ;;  ;; (The DEFSTRUCT used to be in here, but that failed when trying
235        ;;  ;; to cross-compile the hash table implementation.)
236        ;;  ;;(defstruct ,@defstruct-args)
237        ;;  ;; The (SETF (DEF!STRUCT-TYPE-MAKE-LOAD-FORM-FUN ..) ..) used to
238        ;;  ;; be in here too, but that failed an assertion in the SETF
239        ;;  ;; definition once we moved the DEFSTRUCT outside.)
240        ;;  )
241        #+sb-xc-host ,(let ((u (uncross-defstruct-args defstruct-args)))
242                        (if (boundp '*delayed-def!structs*)
243                            `(push (make-delayed-def!struct :args ',u)
244                                   *delayed-def!structs*)
245                            `(sb!xc:defstruct ,@u)))
246        ',name)))
247
248 ;;; When building the cross-compiler, this function has to be called
249 ;;; some time after SB!XC:DEFSTRUCT is set up, in order to take care
250 ;;; of any processing which had to be delayed until then.
251 #+sb-xc-host
252 (defun force-delayed-def!structs ()
253   (if (boundp '*delayed-def!structs*)
254       (progn
255         (mapcar (lambda (x)
256                   (let ((*package* (delayed-def!struct-package x)))
257                     ;; KLUDGE(?): EVAL is almost always the wrong thing.
258                     ;; However, since we have to map DEFSTRUCT over the
259                     ;; list, and since ANSI declined to specify any
260                     ;; functional primitives corresponding to the
261                     ;; DEFSTRUCT macro, it seems to me that EVAL is
262                     ;; required in there somewhere..
263                     (eval `(sb!xc:defstruct ,@(delayed-def!struct-args x)))))
264                 (reverse *delayed-def!structs*))
265         ;; We shouldn't need this list any more. Making it unbound
266         ;; serves as a signal to DEF!STRUCT that it needn't delay
267         ;; DEF!STRUCTs any more. It is also generally a good thing for
268         ;; other reasons: it frees garbage, and it discourages anyone
269         ;; else from pushing anything else onto the list later.
270         (makunbound '*delayed-def!structs*))
271       ;; This condition is probably harmless if it comes up when
272       ;; interactively experimenting with the system by loading a source
273       ;; file into it more than once. But it's worth warning about it
274       ;; because it definitely shouldn't come up in an ordinary build
275       ;; process.
276       (warn "*DELAYED-DEF!STRUCTS* is already unbound.")))
277
278 ;;; The STRUCTURE!OBJECT abstract class is the base of the type
279 ;;; hierarchy for objects which have/use DEF!STRUCT functionality.
280 ;;; (The extra hackery in DEF!STRUCT-defined things isn't needed for
281 ;;; STRUCTURE-OBJECTs defined by ordinary, post-warm-init programs, so
282 ;;; it's only put into STRUCTURE-OBJECTs which inherit from
283 ;;; STRUCTURE!OBJECT.)
284 (def!struct (structure!object (:constructor nil)))
285 \f
286 ;;;; hooking this all into the standard MAKE-LOAD-FORM system
287
288 ;;; MAKE-LOAD-FORM for DEF!STRUCT-defined types
289 (defun structure!object-make-load-form (object &optional env)
290   (declare (ignore env))
291   (funcall (def!struct-type-make-load-form-fun (type-of object))
292            object))
293
294 ;;; Do the right thing at cold load time.
295 ;;;
296 ;;; (Eventually this MAKE-LOAD-FORM function be overwritten by CLOS's
297 ;;; generic MAKE-LOAD-FORM, at which time a STRUCTURE!OBJECT method
298 ;;; should be added to call STRUCTURE!OBJECT-MAKE-LOAD-FORM.)
299 (setf (symbol-function 'sb!xc:make-load-form)
300       #'structure!object-make-load-form)
301
302 ;;; Do the right thing in the vanilla ANSI CLOS of the
303 ;;; cross-compilation host. (Something similar will have to be done in
304 ;;; our CLOS, too, but later, some time long after the toplevel forms
305 ;;; of this file have run.)
306 #+sb-xc-host
307 (defmethod make-load-form ((obj structure!object) &optional (env nil env-p))
308   (if env-p
309       (structure!object-make-load-form obj env)
310       (structure!object-make-load-form obj)))