Declaim types of %%data-vector-...%%.
[sbcl.git] / src / code / target-defstruct.lisp
blob151477d5782ce329f8e31920d322138f2a52e224
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.
10 (in-package "SB!KERNEL")
12 (/show0 "target-defstruct.lisp 12")
14 ;;;; structure frobbing primitives
16 ;;; Allocate a new instance with LENGTH data slots.
17 (defun %make-instance (length)
18 (declare (type index length))
19 (%make-instance length))
21 ;;; Given an instance, return its length.
22 (defun %instance-length (instance)
23 (declare (type instance instance))
24 (%instance-length instance))
26 ;;; Return the value from the INDEXth slot of INSTANCE. This is SETFable.
27 (defun %instance-ref (instance index)
28 (%instance-ref instance index))
30 ;;; Set the INDEXth slot of INSTANCE to NEW-VALUE.
31 (defun %instance-set (instance index new-value)
32 (setf (%instance-ref instance index) new-value))
34 ;;; Normally IR2 converted, definition needed for interpreted structure
35 ;;; constructors only.
36 #!+(or sb-eval sb-fasteval)
37 (defun %make-structure-instance (dd slot-specs &rest slot-values)
38 (let ((instance (%make-instance (dd-instance-length dd))))
39 (setf (%instance-layout instance) (dd-layout-or-lose dd))
40 (mapc (lambda (spec value)
41 (destructuring-bind (raw-type . index) (cdr spec)
42 (macrolet ((make-case ()
43 `(ecase raw-type
44 ((t)
45 (setf (%instance-ref instance index) value))
46 ,@(map 'list
47 (lambda (rsd)
48 `(,(raw-slot-data-raw-type rsd)
49 (setf (,(raw-slot-data-accessor-name rsd)
50 instance index)
51 value)))
52 *raw-slot-data*))))
53 (make-case))))
54 slot-specs slot-values)
55 instance))
57 (defun %raw-instance-ref/word (instance index)
58 (declare (type index index))
59 (%raw-instance-ref/word instance index))
60 (defun %raw-instance-set/word (instance index new-value)
61 (declare (type index index)
62 (type sb!vm:word new-value))
63 (%raw-instance-set/word instance index new-value))
65 (defun %raw-instance-ref/single (instance index)
66 (declare (type index index))
67 (%raw-instance-ref/single instance index))
68 (defun %raw-instance-set/single (instance index new-value)
69 (declare (type index index)
70 (type single-float new-value))
71 (%raw-instance-set/single instance index new-value))
73 (defun %raw-instance-ref/double (instance index)
74 (declare (type index index))
75 (%raw-instance-ref/double instance index))
76 (defun %raw-instance-set/double (instance index new-value)
77 (declare (type index index)
78 (type double-float new-value))
79 (%raw-instance-set/double instance index new-value))
81 (defun %raw-instance-ref/complex-single (instance index)
82 (declare (type index index))
83 (%raw-instance-ref/complex-single instance index))
84 (defun %raw-instance-set/complex-single (instance index new-value)
85 (declare (type index index)
86 (type (complex single-float) new-value))
87 (%raw-instance-set/complex-single instance index new-value))
89 (defun %raw-instance-ref/complex-double (instance index)
90 (declare (type index index))
91 (%raw-instance-ref/complex-double instance index))
92 (defun %raw-instance-set/complex-double (instance index new-value)
93 (declare (type index index)
94 (type (complex double-float) new-value))
95 (%raw-instance-set/complex-double instance index new-value))
97 (defun %instance-layout (instance)
98 (%instance-layout instance))
100 (defun %set-instance-layout (instance new-value)
101 (%set-instance-layout instance new-value))
103 (defun %make-funcallable-instance (len)
104 (%make-funcallable-instance len))
106 (defun funcallable-instance-p (x)
107 (funcallable-instance-p x))
109 (defun %funcallable-instance-info (fin i)
110 (%funcallable-instance-info fin i))
112 (defun %set-funcallable-instance-info (fin i new-value)
113 (%set-funcallable-instance-info fin i new-value))
115 (defun funcallable-instance-fun (fin)
116 (%funcallable-instance-function fin))
118 (defun (setf funcallable-instance-fun) (new-value fin)
119 (setf (%funcallable-instance-function fin) new-value))
121 ;;;; target-only parts of the DEFSTRUCT top level code
123 ;;; A list of hooks designating functions of one argument, the
124 ;;; classoid, to be called when a defstruct is evaluated.
125 (!defvar *defstruct-hooks* nil)
127 ;;; the part of %DEFSTRUCT which makes sense only on the target SBCL
129 (defun %target-defstruct (dd)
130 (declare (type defstruct-description dd))
132 (/show0 "entering %TARGET-DEFSTRUCT")
134 (when (dd-doc dd)
135 (setf (fdocumentation (dd-name dd) 'structure)
136 (dd-doc dd)))
138 (let* ((classoid (find-classoid (dd-name dd)))
139 (layout (classoid-layout classoid)))
140 (when (eq (dd-pure dd) t)
141 (setf (layout-pure layout) t))
142 #!+interleaved-raw-slots
143 ;; Make a vector of EQUALP slots comparators, indexed by (- word-index data-start).
144 ;; This has to be assigned to something regardless of whether there are
145 ;; raw slots just in case someone mutates a layout which had raw
146 ;; slots into one which does not - although that would probably crash
147 ;; unless no instances exist or all raw slots miraculously contained
148 ;; bits which were the equivalent of valid Lisp descriptors.
150 ;; It's not worth adding a #-interleaved-raw-slots case to this optimization
151 ;; because every architecture can be made to use the new approach.
152 (setf (layout-equalp-tests layout)
153 (if (zerop (layout-untagged-bitmap layout))
155 ;; The initial element of NIL means "do not compare".
156 ;; Ignored words (comparator = NIL) fall into two categories:
157 ;; - pseudo-ignored, which get compared by their
158 ;; predecessor word, as for complex-double-float,
159 ;; - internal padding words which are truly ignored.
160 ;; Other words are compared as tagged if the comparator is 0,
161 ;; or as untagged if the comparator is a type-specific function.
162 (let ((comparators
163 ;; If data-start is 1, subtract 1 because we don't need
164 ;; a comparator for the LAYOUT slot.
165 (make-array (- (dd-length dd) sb!vm:instance-data-start)
166 :initial-element nil)))
167 (dolist (slot (dd-slots dd) comparators)
168 ;; -1 because LAYOUT (slot index 0) has no comparator stored.
169 (setf (aref comparators
170 (- (dsd-index slot) sb!vm:instance-data-start))
171 (let ((rsd (dsd-raw-slot-data slot)))
172 (if (not rsd)
173 0 ; means recurse using EQUALP
174 (raw-slot-data-comparer rsd))))))))
176 (dolist (fun *defstruct-hooks*)
177 (funcall fun classoid)))
179 (/show0 "leaving %TARGET-DEFSTRUCT")
180 (values))
182 ;;; Copy any old kind of structure.
183 (defun copy-structure (structure)
184 #!+sb-doc
185 "Return a copy of STRUCTURE with the same (EQL) slot values."
186 (declare (type structure-object structure))
187 (let ((layout (%instance-layout structure)))
188 (when (layout-invalid layout)
189 (error "attempt to copy an obsolete structure:~% ~S" structure))
190 (let ((res (%make-instance (%instance-length structure)))
191 (len (layout-length layout)))
192 (declare (type index len))
193 #!-interleaved-raw-slots
194 (let ((nuntagged (layout-n-untagged-slots layout)))
195 ;; Copy ordinary slots including the layout.
196 (dotimes (i (- len nuntagged))
197 (declare (type index i))
198 (setf (%instance-ref res i) (%instance-ref structure i)))
199 ;; Copy raw slots.
200 (dotimes (i nuntagged)
201 (declare (type index i))
202 (setf (%raw-instance-ref/word res i)
203 (%raw-instance-ref/word structure i))))
204 #!+interleaved-raw-slots
205 (let ((metadata (layout-untagged-bitmap layout)))
206 ;; Don't assume that %INSTANCE-REF can access the layout.
207 (setf (%instance-layout res) (%instance-layout structure))
208 ;; With interleaved slots, the only difference between %instance-ref
209 ;; and %raw-instance-ref/word is the storage class of the VOP operands.
210 ;; Since x86(-64) doesn't partition the register set, the bitmap test
211 ;; could be skipped if we wanted to copy everything as raw.
212 (macrolet ((copy-loop (raw-p &optional step)
213 `(do ((i sb!vm:instance-data-start (1+ i)))
214 ((>= i len))
215 (declare (index i))
216 (if ,raw-p
217 (setf (%raw-instance-ref/word res i)
218 (%raw-instance-ref/word structure i))
219 (setf (%instance-ref res i)
220 (%instance-ref structure i)))
221 ,step)))
222 (cond ((zerop metadata) ; no untagged slots.
223 (copy-loop nil))
224 ;; The fixnum case uses fixnum operations for ODDP and ASH.
225 ((fixnump metadata) ; shift and mask is faster than logbitp
226 (copy-loop (oddp (truly-the fixnum metadata))
227 (setq metadata (ash metadata -1))))
228 (t ; bignum - use LOGBITP to avoid consing more bignums
229 (copy-loop (logbitp i metadata))))))
230 res)))
233 ;; Do an EQUALP comparison on the raw slots (only, not the normal slots) of a
234 ;; structure.
235 #!-interleaved-raw-slots
236 (defun raw-instance-slots-equalp (layout x y)
237 ;; This implementation sucks, but hopefully EQUALP on raw structures
238 ;; won't be a major bottleneck for anyone. It'd be tempting to do
239 ;; all this with %RAW-INSTANCE-REF/WORD and bitwise comparisons, but
240 ;; that'll fail in some cases. For example -0.0 and 0.0 are EQUALP
241 ;; but have different bit patterns. -- JES, 2007-08-21
242 (loop for dsd in (dd-slots (layout-info layout))
243 for raw-type-index = (dsd-%raw-type dsd)
244 always (or (eql raw-type-index -1)
245 (funcall (raw-slot-data-comparer
246 (svref *raw-slot-data* raw-type-index))
247 (dsd-index dsd) x y))))
249 ;;; default PRINT-OBJECT method
251 ;;; Printing formerly called the auto-generated accessor functions,
252 ;;; but reading the slots more primitively confers several advantages:
253 ;;; - it works even if the user clobbered an accessor
254 ;;; - it works if the slot fails a type-check and the reader was SAFE-P,
255 ;; i.e. was required to perform a check. This is a feature, not a bug.
256 (macrolet ((access-fn (dsd)
257 `(acond ((dsd-raw-slot-data ,dsd)
258 (symbol-function (raw-slot-data-accessor-name it)))
259 (t #'%instance-ref))))
261 (defun %default-structure-pretty-print (structure stream name dd)
262 (pprint-logical-block (stream nil :prefix "#S(" :suffix ")")
263 (prin1 name stream)
264 (let ((remaining-slots (dd-slots dd)))
265 (when remaining-slots
266 (write-char #\space stream)
267 ;; CMU CL had (PPRINT-INDENT :BLOCK 2 STREAM) here,
268 ;; but I can't see why. -- WHN 20000205
269 (pprint-newline :linear stream)
270 (loop (pprint-pop)
271 (let ((slot (pop remaining-slots)))
272 (write-char #\: stream)
273 (output-symbol-name (symbol-name (dsd-name slot)) stream)
274 (write-char #\space stream)
275 (pprint-newline :miser stream)
276 (output-object (funcall (access-fn slot) structure (dsd-index slot))
277 stream)
278 (when (null remaining-slots)
279 (return))
280 (write-char #\space stream)
281 (pprint-newline :linear stream)))))))
283 (defun %default-structure-ugly-print (structure stream name dd)
284 (descend-into (stream)
285 (write-string "#S(" stream)
286 (prin1 name stream)
287 (do ((index 0 (1+ index))
288 (limit (or (and (not *print-readably*) *print-length*)
289 most-positive-fixnum))
290 (remaining-slots (dd-slots dd) (cdr remaining-slots)))
291 ((or (null remaining-slots) (>= index limit))
292 (write-string (if remaining-slots " ...)" ")") stream))
293 (declare (type index index))
294 (write-string " :" stream)
295 (let ((slot (first remaining-slots)))
296 (output-symbol-name (symbol-name (dsd-name slot)) stream)
297 (write-char #\space stream)
298 (output-object (funcall (access-fn slot) structure (dsd-index slot))
299 stream)))))
300 ) ; end MACROLET
302 (defun default-structure-print (structure stream depth)
303 (declare (ignore depth))
304 (if (funcallable-instance-p structure)
305 (print-unreadable-object (structure stream :identity t :type t))
306 (let* ((layout (%instance-layout structure))
307 (dd (layout-info layout))
308 (name (classoid-name (layout-classoid layout))))
309 (cond ((not dd)
310 ;; FIXME? this branch may be unnecessary as a consequence
311 ;; of change f02bee325920166b69070e4735a8a3f295f8edfd which
312 ;; stopped the badness is a stronger way. It should be the case
313 ;; that absence of a DD can't happen unless the classoid is absent.
314 ;; KLUDGE: during PCL build debugging, we can sometimes
315 ;; attempt to print out a PCL object (with null LAYOUT-INFO).
316 (pprint-logical-block (stream nil :prefix "#<" :suffix ">")
317 (prin1 name stream)
318 (write-char #\space stream)
319 (write-string "(no LAYOUT-INFO)" stream)))
320 ((not (dd-slots dd))
321 ;; the structure type doesn't count as a component for *PRINT-LEVEL*
322 ;; processing. We can likewise elide the logical block processing,
323 ;; since all we have to print is the type name. -- CSR, 2004-10-05
324 (write-string "#S(" stream)
325 (prin1 name stream)
326 (write-char #\) stream))
328 (funcall (if *print-pretty*
329 #'%default-structure-pretty-print
330 #'%default-structure-ugly-print)
331 structure stream name dd))))))
333 (def!method print-object ((x structure-object) stream)
334 (default-structure-print x stream *current-level-in-print*))
336 ;; This generates a sexpr that can be recognized as having a particular
337 ;; shape so that the dumping mechanism can decide if it is or is not
338 ;; necessary to run that code through the main compiler - FASL operations
339 ;; can be used in the case that all slots are preserved.
340 ;; In particular, there are no gensyms in the result, so that calling this
341 ;; twice on the same object yields the same list as compared by EQUAL.
342 (defun structure-obj-slot-saving-forms (struct slot-names slot-names-p)
343 (let* ((layout (%instance-layout struct))
344 (dd (layout-info layout)))
345 (mapcan (lambda (dsd)
346 (when (or (not slot-names-p) (memq (dsd-name dsd) slot-names))
347 (let ((index (dsd-index dsd))
348 (rsd (dsd-raw-slot-data dsd)))
349 (if (not rsd)
350 `((%instance-ref ,struct ,index)
351 ,(let ((val (%instance-ref struct index)))
352 (if (and (or (listp val) (symbolp val))
353 (not (member val '(nil t))))
354 (list 'quote val)
355 val)))
356 (let ((accessor (raw-slot-data-accessor-name rsd)))
357 `((,accessor ,struct ,index)
358 ,(funcall accessor struct index)))))))
359 (dd-slots dd))))
361 ;; Return T if CREATION-FORM and INIT-FORM would have the identical effect
362 ;; as :SB-JUST-DUMP-IT-NORMALLY for STRUCT. MAKE-LOAD-FORM-SAVING-SLOTS can't
363 ;; merely return the magic token (when possible) because a user application
364 ;; could call MAKE-LOAD-FORM-SAVING-SLOTS to obtain forms that can be evaluated
365 ;; or otherwise examined. So instead we scan the code and detect whether it is
366 ;; identical to what was returned from a trivial use of M-L-F-S-S.
367 (defun canonical-slot-saving-forms-p (struct creation-form init-form)
368 (and (sb!c::canonical-instance-maker-form-p creation-form)
369 (typep init-form '(cons (eql setf)))
370 (eq (cadr (cadr (cadr creation-form))) (class-name (class-of struct)))
371 (= (length (dd-slots (layout-info (%instance-layout struct))))
372 (ash (list-length (cdr init-form)) -1))
373 (flet ((eq-quoted-p (a b)
374 (and (typep a '(cons (eql quote) (cons t null)))
375 (typep b '(cons (eql quote) (cons t null)))
376 (eq (cadr a) (cadr b)))))
377 ;; Naively, EQUALP would almost work to compare the slot assignments,
378 ;; but we must not get stuck in circular lists, so traverse by hand.
379 (loop for (expect-place expect-value)
380 on (structure-obj-slot-saving-forms struct nil nil) by #'cddr
381 for (actual-place actual-value) on (cdr init-form) by #'cddr
382 always (and (equal actual-place expect-place)
383 ;; Use EQL, not EQ. Values come from the identical
384 ;; struct, but reading a raw slot can create new
385 ;; pointers. For QUOTE forms, EQ is ok.
386 (or (eql actual-value expect-value)
387 (eq-quoted-p actual-value expect-value)))))))
389 (/show0 "target-defstruct.lisp end of file")