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