Initial revision
[sbcl.git] / src / code / target-defstruct.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 the CMU CL system, which was
5 ;;;; written at Carnegie Mellon University and released into the
6 ;;;; public domain. The software is in the public domain and is
7 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
8 ;;;; files for more information.
9
10 (in-package "SB!KERNEL")
11
12 (file-comment
13   "$Header$")
14 \f
15 ;;;; structure frobbing primitives
16
17 (defun %make-instance (length)
18   #!+sb-doc
19   "Allocate a new instance with LENGTH data slots."
20   (declare (type index length))
21   (%make-instance length))
22
23 (defun %instance-length (instance)
24   #!+sb-doc
25   "Given an instance, return its length."
26   (declare (type instance instance))
27   (%instance-length instance))
28
29 (defun %instance-ref (instance index)
30   #!+sb-doc
31   "Return the value from the INDEXth slot of INSTANCE. This is SETFable."
32   (%instance-ref instance index))
33
34 (defun %instance-set (instance index new-value)
35   #!+sb-doc
36   "Set the INDEXth slot of INSTANCE to NEW-VALUE."
37   (setf (%instance-ref instance index) new-value))
38
39 (defun %raw-ref-single (vec index)
40   (declare (type index index))
41   (%raw-ref-single vec index))
42
43 (defun %raw-ref-double (vec index)
44   (declare (type index index))
45   (%raw-ref-double vec index))
46
47 #!+long-float
48 (defun %raw-ref-long (vec index)
49   (declare (type index index))
50   (%raw-ref-long vec index))
51
52 (defun %raw-set-single (vec index val)
53   (declare (type index index))
54   (%raw-set-single vec index val))
55
56 (defun %raw-set-double (vec index val)
57   (declare (type index index))
58   (%raw-set-double vec index val))
59
60 #!+long-float
61 (defun %raw-set-long (vec index val)
62   (declare (type index index))
63   (%raw-set-long vec index val))
64
65 (defun %raw-ref-complex-single (vec index)
66   (declare (type index index))
67   (%raw-ref-complex-single vec index))
68
69 (defun %raw-ref-complex-double (vec index)
70   (declare (type index index))
71   (%raw-ref-complex-double vec index))
72
73 #!+long-float
74 (defun %raw-ref-complex-long (vec index)
75   (declare (type index index))
76   (%raw-ref-complex-long vec index))
77
78 (defun %raw-set-complex-single (vec index val)
79   (declare (type index index))
80   (%raw-set-complex-single vec index val))
81
82 (defun %raw-set-complex-double (vec index val)
83   (declare (type index index))
84   (%raw-set-complex-double vec index val))
85
86 #!+long-float
87 (defun %raw-set-complex-long (vec index val)
88   (declare (type index index))
89   (%raw-set-complex-long vec index val))
90
91 (defun %instance-layout (instance)
92   (%instance-layout instance))
93
94 (defun %set-instance-layout (instance new-value)
95   (%set-instance-layout instance new-value))
96
97 (defun %make-funcallable-instance (len layout)
98    (%make-funcallable-instance len layout))
99
100 (defun funcallable-instance-p (x) (funcallable-instance-p x))
101
102 (defun %funcallable-instance-info (fin i)
103   (%funcallable-instance-info fin i))
104
105 (defun %set-funcallable-instance-info (fin i new-value)
106   (%set-funcallable-instance-info fin i new-value))
107
108 (defun funcallable-instance-function (fin)
109   (%funcallable-instance-lexenv fin))
110
111 ;;; The heart of the magic of funcallable instances ("FINs"). The
112 ;;; function for a FIN must be a magical INSTANCE-LAMBDA form. When
113 ;;; called (as with any other function), we grab the code pointer, and
114 ;;; call it, leaving the original function object in LEXENV (in case
115 ;;; it was a closure). If it is actually a FIN, then we need to do an
116 ;;; extra indirection with funcallable-instance-lexenv to get at any
117 ;;; closure environment. This extra indirection is set up when
118 ;;; accessing the closure environment of an INSTANCE-LAMBDA. Note that
119 ;;; the original FIN pointer is lost, so if the called function wants
120 ;;; to get at the original object to do some slot accesses, it must
121 ;;; close over the FIN object.
122 ;;;
123 ;;; If we set the FIN function to be a FIN, we directly copy across
124 ;;; both the code pointer and the lexenv, since that code pointer (for
125 ;;; an instance-lambda) is expecting that lexenv to be accessed. This
126 ;;; effectively pre-flattens what would otherwise be a chain of
127 ;;; indirections. Lest this sound like an excessively obscure case,
128 ;;; note that it happens when PCL dispatch functions are
129 ;;; byte-compiled.
130 ;;;
131 ;;; The only loss is that if someone accesses the
132 ;;; FUNCALLABLE-INSTANCE-FUNCTION, then won't get a FIN back. This
133 ;;; probably doesn't matter, since PCL only sets the FIN function. And
134 ;;; the only reason that interpreted functions are FINs instead of
135 ;;; bare closures is for debuggability.
136 (defun (setf funcallable-instance-function) (new-value fin)
137   (setf (%funcallable-instance-function fin)
138         (%closure-function new-value))
139   (setf (%funcallable-instance-lexenv fin)
140         (if (funcallable-instance-p new-value)
141             (%funcallable-instance-lexenv new-value)
142             new-value)))
143 \f
144 ;;; Copy any old kind of structure.
145 (defun copy-structure (structure)
146   #!+sb-doc
147   "Return a copy of STRUCTURE with the same (EQL) slot values."
148   (declare (type structure-object structure))
149   (let* ((len (%instance-length structure))
150          (res (%make-instance len))
151          (layout (%instance-layout structure)))
152
153     (declare (type index len))
154     (when (layout-invalid layout)
155       (error "attempt to copy an obsolete structure:~%  ~S" structure))
156
157     ;; Copy ordinary slots.
158     (dotimes (i len)
159       (declare (type index i))
160       (setf (%instance-ref res i)
161             (%instance-ref structure i)))
162
163     ;; Copy raw slots.
164     (let ((raw-index (dd-raw-index (layout-info layout))))
165       (when raw-index
166         (let* ((data (%instance-ref structure raw-index))
167                (raw-len (length data))
168                (new (make-array raw-len :element-type '(unsigned-byte 32))))
169           (declare (type (simple-array (unsigned-byte 32) (*)) data))
170           (setf (%instance-ref res raw-index) new)
171           (dotimes (i raw-len)
172             (setf (aref new i) (aref data i))))))
173
174     res))
175 \f
176 ;;; default PRINT and MAKE-LOAD-FORM methods
177
178 (defun default-structure-print (structure stream depth)
179   (declare (ignore depth))
180   (if (funcallable-instance-p structure)
181       (print-unreadable-object (structure stream :identity t :type t))
182       (let* ((type (%instance-layout structure))
183              (name (sb!xc:class-name (layout-class type)))
184              (dd (layout-info type)))
185         (if *print-pretty*
186             (pprint-logical-block (stream nil :prefix "#S(" :suffix ")")
187               (prin1 name stream)
188               (let ((slots (dd-slots dd)))
189                 (when slots
190                   (write-char #\space stream)
191                   ;; CMU CL had (PPRINT-INDENT :BLOCK 2 STREAM) here,
192                   ;; but I can't see why. -- WHN 20000205
193                   (pprint-newline :linear stream)
194                   (loop
195                     (pprint-pop)
196                     (let ((slot (pop slots)))
197                       (write-char #\: stream)
198                       (output-symbol-name (dsd-%name slot) stream)
199                       (write-char #\space stream)
200                       (pprint-newline :miser stream)
201                       (output-object (funcall (fdefinition (dsd-accessor slot))
202                                               structure)
203                                      stream)
204                       (when (null slots)
205                         (return))
206                       (write-char #\space stream)
207                       (pprint-newline :linear stream))))))
208             (descend-into (stream)
209               (write-string "#S(" stream)
210               (prin1 name stream)
211               (do ((index 0 (1+ index))
212                    (slots (dd-slots dd) (cdr slots)))
213                   ((or (null slots)
214                        (and (not *print-readably*)
215                             (>= index *print-length*)))
216                    (if (null slots)
217                        (write-string ")" stream)
218                        (write-string " ...)" stream)))
219                 (declare (type index index))
220                 (write-char #\space stream)
221                 (write-char #\: stream)
222                 (let ((slot (first slots)))
223                   (output-symbol-name (dsd-%name slot) stream)
224                   (write-char #\space stream)
225                   (output-object (funcall (fdefinition (dsd-accessor slot))
226                                           structure)
227                                  stream))))))))
228 (def!method print-object ((x structure-object) stream)
229   (default-structure-print x stream *current-level*))
230
231 (defun make-load-form-saving-slots (object &key slot-names environment)
232   (declare (ignore object environment))
233   (if slot-names
234     (error "stub: MAKE-LOAD-FORM-SAVING-SLOTS :SLOT-NAMES not implemented") ; KLUDGE
235     :just-dump-it-normally))
236 \f
237 ;;; Return true if OBJ is an object of the structure type
238 ;;; corresponding to LAYOUT. This is called by the accessor closures,
239 ;;; which have a handle on the type's layout.
240 ;;;
241 ;;; FIXME: This is fairly big, so it should probably become
242 ;;; MAYBE-INLINE instead of INLINE. Or else we could fix things up so
243 ;;; that the things which call it are all closures, so that it's
244 ;;; expanded only in a small number of places.
245 #!-sb-fluid (declaim (inline typep-to-layout))
246 (defun typep-to-layout (obj layout)
247   (declare (type layout layout) (optimize (speed 3) (safety 0)))
248   (when (layout-invalid layout)
249     (error "An obsolete structure accessor function was called."))
250   ;; FIXME: CMU CL used (%INSTANCEP OBJ) here. Check that
251   ;; (TYPEP OBJ 'INSTANCE) is optimized to equally efficient code.
252   (and (typep obj 'instance)
253        (let (;; FIXME: Mightn't there be a slight efficiency improvement
254              ;; by delaying the binding of DEPTHOID 'til it's needed?
255              (depthoid (layout-depthoid layout))
256              (obj-layout (%instance-layout obj)))
257          (cond ((eq obj-layout layout)
258                 t)
259                ;; FIXME: Does the test for LAYOUT-INVALID really belong
260                ;; after the test for EQ LAYOUT? Either explain why this
261                ;; is, or change the order.
262                ((layout-invalid obj-layout)
263                 (error 'layout-invalid
264                        :expected-type (layout-class obj-layout)
265                        :datum obj))
266                (t
267                 (and (> (layout-depthoid obj-layout) depthoid)
268                      (eq (svref (layout-inherits obj-layout) depthoid)
269                          layout)))))))
270 \f
271 ;;;; implementing structure slot accessors as closures
272
273 ;;; In the normal case of structures that have a real type (i.e. no
274 ;;; :TYPE option was specified), we want to optimize things for space
275 ;;; as well as speed, since there can be thousands of defined slot
276 ;;; accessors.
277 ;;;
278 ;;; What we do is define the accessors and copier as closures over
279 ;;; general-case code. Since the compiler will normally open-code
280 ;;; accessors, the (minor) extra speed penalty for full calls is not a
281 ;;; concern.
282 ;;;
283 ;;; KLUDGE: This is a minor headache at cold init time, since genesis
284 ;;; doesn't know how to create the closures in the cold image, so the
285 ;;; function definitions aren't done until the appropriate top level
286 ;;; forms are executed, so any forward references to structure slots
287 ;;; (which are compiled into full calls) fail. The headache can be
288 ;;; treated by using SB!XC:DEFSTRUCT on the relevant structure at
289 ;;; build-the-cross-compiler time, so that the compiler is born
290 ;;; knowing how to inline accesses to the relevant structure, so no
291 ;;; full calls are made. This can be achieved by calling
292 ;;; SB!XC:DEFSTRUCT directly, or by using DEF!STRUCT, which (among
293 ;;; other things) calls SB!XC:DEFSTRUCT for you.
294
295 ;;; Return closures to do slot access according to Layout and DSD. We check
296 ;;; types, then do the access. This is only used for normal slots, not raw
297 ;;; slots.
298 (defun structure-slot-getter (layout dsd)
299   (let ((class (layout-class layout)))
300     (if (typep class 'basic-structure-class)
301         #'(lambda (structure)
302             (declare (optimize (speed 3) (safety 0)))
303             (flet ((structure-test (structure)
304                      (typep-to-layout structure layout)))
305               (unless (structure-test structure)
306                 (error 'simple-type-error
307                        :datum structure
308                        ;; FIXME: :EXPECTED-TYPE should be something
309                        ;; comprehensible to the user, not this. Perhaps we
310                        ;; could work backwards from the LAYOUT-CLASS slot to
311                        ;; find something. (Note that all four SIMPLE-TYPE-ERROR
312                        ;; calls in this section have the same disease.)
313                        :expected-type '(satisfies structure-test)
314                        :format-control
315                        "Structure for accessor ~S is not a ~S:~% ~S"
316                        :format-arguments
317                        (list (dsd-accessor dsd)
318                              (sb!xc:class-name (layout-class layout))
319                              structure))))
320             (%instance-ref structure (dsd-index dsd)))
321         #'(lambda (structure)
322             (declare (optimize (speed 3) (safety 0)))
323             (unless (%typep structure class)
324               (error 'simple-type-error
325                      :datum structure
326                      :expected-type 'class
327                      :format-control
328                      "The structure for accessor ~S is not a ~S:~% ~S"
329                      :format-arguments
330                      (list (dsd-accessor dsd) class
331                            structure)))
332             (%instance-ref structure (dsd-index dsd))))))
333 (defun structure-slot-setter (layout dsd)
334   (let ((class (layout-class layout)))
335     (if (typep class 'basic-structure-class)
336         #'(lambda (new-value structure)
337             (declare (optimize (speed 3) (safety 0)))
338             (flet ((structure-test (structure)
339                      (typep-to-layout structure layout))
340                    (typep-test (new-value)
341                      (%typep new-value (dsd-type dsd))))
342               (unless (structure-test structure)
343                 (error 'simple-type-error
344                        :datum structure
345                        :expected-type '(satisfies structure-test)
346                        :format-control
347                        "The structure for setter ~S is not a ~S:~% ~S"
348                        :format-arguments
349                        (list `(setf ,(dsd-accessor dsd))
350                              (sb!xc:class-name (layout-class layout))
351                              structure)))
352               (unless  (typep-test new-value)
353                 (error 'simple-type-error
354                        :datum new-value
355                        :expected-type '(satisfies typep-test)
356                        :format-control
357                        "The new value for setter ~S is not a ~S:~% ~S"
358                        :format-arguments
359                        (list `(setf ,(dsd-accessor dsd))
360                               (dsd-type dsd)
361                               new-value))))
362             (setf (%instance-ref structure (dsd-index dsd)) new-value))
363         #'(lambda (new-value structure)
364             (declare (optimize (speed 3) (safety 0)))
365             (flet ((structure-test (structure)
366                      (sb!xc:typep structure class))
367                    (typep-test (new-value)
368                      (%typep new-value (dsd-type dsd))))
369               (unless (structure-test structure)
370                 (error 'simple-type-error
371                        :datum structure
372                        :expected-type '(satisfies structure-test)
373                        :format-control
374                        "The structure for setter ~S is not a ~S:~% ~S"
375                        :format-arguments
376                        (list `(setf ,(dsd-accessor dsd))
377                              (sb!xc:class-name class)
378                              structure)))
379               (unless  (typep-test new-value)
380                 (error 'simple-type-error
381                        :datum new-value
382                        :expected-type '(satisfies typep-test)
383                        :format-control
384                        "The new value for setter ~S is not a ~S:~% ~S"
385                        :format-arguments
386                        (list `(setf ,(dsd-accessor dsd))
387                              (dsd-type dsd)
388                              new-value))))
389             (setf (%instance-ref structure (dsd-index dsd)) new-value)))))