1.0.8.44: Fix EQUALP on structures with raw slots
[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 ;;; Allocate a new instance with LENGTH data slots.
17 (defun %make-instance (length)
18   (declare (type index length))
19   (%make-instance length))
20
21 ;;; Given an instance, return its length.
22 (defun %instance-length (instance)
23   (declare (type instance instance))
24   (%instance-length instance))
25
26 ;;; Return the value from the INDEXth slot of INSTANCE. This is SETFable.
27 (defun %instance-ref (instance index)
28   (%instance-ref instance index))
29
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))
33
34 #!-hppa
35 (progn
36   (defun %raw-instance-ref/word (instance index)
37     (declare (type index index))
38     (%raw-instance-ref/word instance index))
39   (defun %raw-instance-set/word (instance index new-value)
40     (declare (type index index)
41              (type sb!vm:word new-value))
42     (%raw-instance-set/word instance index new-value))
43
44   (defun %raw-instance-ref/single (instance index)
45     (declare (type index index))
46     (%raw-instance-ref/single instance index))
47   (defun %raw-instance-set/single (instance index new-value)
48     (declare (type index index)
49              (type single-float new-value))
50     (%raw-instance-set/single instance index new-value))
51
52   (defun %raw-instance-ref/double (instance index)
53     (declare (type index index))
54     (%raw-instance-ref/double instance index))
55   (defun %raw-instance-set/double (instance index new-value)
56     (declare (type index index)
57              (type double-float new-value))
58     (%raw-instance-set/double instance index new-value))
59
60   (defun %raw-instance-ref/complex-single (instance index)
61     (declare (type index index))
62     (%raw-instance-ref/complex-single instance index))
63   (defun %raw-instance-set/complex-single (instance index new-value)
64     (declare (type index index)
65              (type (complex single-float) new-value))
66     (%raw-instance-set/complex-single instance index new-value))
67
68   (defun %raw-instance-ref/complex-double (instance index)
69     (declare (type index index))
70     (%raw-instance-ref/complex-double instance index))
71   (defun %raw-instance-set/complex-double (instance index new-value)
72     (declare (type index index)
73              (type (complex double-float) new-value))
74     (%raw-instance-set/complex-double instance index new-value))
75 ) ; #!-HPPA
76
77 #!+hppa
78 (progn
79 (defun %raw-ref-single (vec index)
80   (declare (type index index))
81   (%raw-ref-single vec index))
82
83 (defun %raw-ref-double (vec index)
84   (declare (type index index))
85   (%raw-ref-double vec index))
86
87 #!+long-float
88 (defun %raw-ref-long (vec index)
89   (declare (type index index))
90   (%raw-ref-long vec index))
91
92 (defun %raw-set-single (vec index val)
93   (declare (type index index))
94   (%raw-set-single vec index val))
95
96 (defun %raw-set-double (vec index val)
97   (declare (type index index))
98   (%raw-set-double vec index val))
99
100 #!+long-float
101 (defun %raw-set-long (vec index val)
102   (declare (type index index))
103   (%raw-set-long vec index val))
104
105 (defun %raw-ref-complex-single (vec index)
106   (declare (type index index))
107   (%raw-ref-complex-single vec index))
108
109 (defun %raw-ref-complex-double (vec index)
110   (declare (type index index))
111   (%raw-ref-complex-double vec index))
112
113 #!+long-float
114 (defun %raw-ref-complex-long (vec index)
115   (declare (type index index))
116   (%raw-ref-complex-long vec index))
117
118 (defun %raw-set-complex-single (vec index val)
119   (declare (type index index))
120   (%raw-set-complex-single vec index val))
121
122 (defun %raw-set-complex-double (vec index val)
123   (declare (type index index))
124   (%raw-set-complex-double vec index val))
125
126 #!+long-float
127 (defun %raw-set-complex-long (vec index val)
128   (declare (type index index))
129   (%raw-set-complex-long vec index val))
130 ) ; #!+HPPA
131
132 (defun %instance-layout (instance)
133   (%instance-layout instance))
134
135 (defun %set-instance-layout (instance new-value)
136   (%set-instance-layout instance new-value))
137
138 (defun %make-funcallable-instance (len)
139   (%make-funcallable-instance len))
140
141 (defun funcallable-instance-p (x) (funcallable-instance-p x))
142
143 (defun %funcallable-instance-info (fin i)
144   (%funcallable-instance-info fin i))
145
146 (defun %set-funcallable-instance-info (fin i new-value)
147   (%set-funcallable-instance-info fin i new-value))
148
149 (defun funcallable-instance-fun (fin)
150   (%funcallable-instance-function fin))
151
152 (defun (setf funcallable-instance-fun) (new-value fin)
153   (setf (%funcallable-instance-function fin) new-value))
154
155 ;;; service function for structure constructors
156 (defun %make-instance-with-layout (layout)
157   ;; Make sure the object ends at a two-word boundary.  Note that this does
158   ;; not affect the amount of memory used, since the allocator would add the
159   ;; same padding anyway.  However, raw slots are indexed from the length of
160   ;; the object as indicated in the header, so the pad word needs to be
161   ;; included in that length to guarantee proper alignment of raw double float
162   ;; slots, necessary for (at least) the SPARC backend.
163   (let* ((length (layout-length layout))
164          (result (%make-instance (+ length (mod (1+ length) 2)))))
165     (setf (%instance-layout result) layout)
166     result))
167 \f
168 ;;;; target-only parts of the DEFSTRUCT top level code
169
170 ;;; A list of hooks designating functions of one argument, the
171 ;;; classoid, to be called when a defstruct is evaluated.
172 (defvar *defstruct-hooks* nil)
173
174 ;;; Catch attempts to mess up definitions of symbols in the CL package.
175 (defun protect-cl (symbol)
176   (/show0 "entering PROTECT-CL, SYMBOL=..")
177   (/hexstr symbol)
178   (when (and *cold-init-complete-p*
179              (eq (symbol-package symbol) *cl-package*))
180     (cerror "Go ahead and patch the system."
181             "attempting to modify a symbol in the COMMON-LISP package: ~S"
182             symbol))
183   (/show0 "leaving PROTECT-CL")
184   (values))
185
186 ;;; the part of %DEFSTRUCT which makes sense only on the target SBCL
187 ;;;
188 ;;; (The "static" in the name is because it needs to be done not only
189 ;;; in ordinary toplevel %DEFSTRUCT, but also in cold init as early as
190 ;;; possible, to simulate static linking of structure functions as
191 ;;; nearly as possible.)
192 (defun %target-defstruct (dd layout)
193   (declare (type defstruct-description dd))
194   (declare (type layout layout))
195
196   (/show0 "entering %TARGET-DEFSTRUCT")
197
198   (remhash (dd-name dd) *typecheckfuns*)
199
200   ;; (Constructors aren't set up here, because constructors are
201   ;; varied enough (possibly parsing any specified argument list)
202   ;; that we can't reasonably implement them as closures, so we
203   ;; implement them with DEFUN instead.)
204
205   ;; Set FDEFINITIONs for slot accessors.
206   (dolist (dsd (dd-slots dd))
207     (/show0 "doing FDEFINITION for slot accessor")
208     (let ((accessor-name (dsd-accessor-name dsd)))
209       ;; We mustn't step on any inherited accessors
210       (unless (accessor-inherited-data accessor-name dd)
211         (/show0 "ACCESSOR-NAME=..")
212         (/hexstr accessor-name)
213         (protect-cl accessor-name)
214         (/hexstr "getting READER-FUN and WRITER-FUN")
215         (multiple-value-bind (reader-fun writer-fun)
216             (slot-accessor-funs dd dsd)
217           (declare (type function reader-fun writer-fun))
218           (/show0 "got READER-FUN and WRITER-FUN=..")
219           (/hexstr reader-fun)
220           (setf (symbol-function accessor-name) reader-fun)
221           (unless (dsd-read-only dsd)
222             (/show0 "setting FDEFINITION for WRITER-FUN=..")
223             (/hexstr writer-fun)
224             (setf (fdefinition `(setf ,accessor-name)) writer-fun))))))
225
226   ;; Set FDEFINITION for copier.
227   (when (dd-copier-name dd)
228     (/show0 "doing FDEFINITION for copier")
229     (protect-cl (dd-copier-name dd))
230     ;; We can't use COPY-STRUCTURE for other kinds of objects, notably
231     ;; funcallable structures, since it returns a STRUCTURE-OBJECT.
232     ;; (And funcallable instances don't need copiers anyway.)
233     (aver (eql (dd-type dd) 'structure))
234     (setf (symbol-function (dd-copier-name dd))
235           ;; FIXME: should use a closure which checks arg type before copying
236           #'copy-structure))
237
238   ;; Set FDEFINITION for predicate.
239   (when (dd-predicate-name dd)
240     (/show0 "doing FDEFINITION for predicate")
241     (protect-cl (dd-predicate-name dd))
242     (setf (symbol-function (dd-predicate-name dd))
243           (ecase (dd-type dd)
244             ;; structures with LAYOUTs
245             ((structure funcallable-structure)
246              (/show0 "with-LAYOUT case")
247              (lambda (object)
248                (locally ; <- to keep SAFETY 0 from affecting arg count checking
249                  (declare (optimize (speed 3) (safety 0)))
250                  (/noshow0 "in with-LAYOUT structure predicate closure, OBJECT,LAYOUT=..")
251                  (/nohexstr object)
252                  (/nohexstr layout)
253                  (typep-to-layout object layout))))
254             ;; structures with no LAYOUT (i.e. :TYPE VECTOR or :TYPE LIST)
255             ;;
256             ;; FIXME: should handle the :NAMED T case in these cases
257             (vector
258              (/show0 ":TYPE VECTOR case")
259              #'vectorp)
260             (list
261              (/show0 ":TYPE LIST case")
262              #'listp))))
263
264   (when (dd-doc dd)
265     (setf (fdocumentation (dd-name dd) 'structure)
266           (dd-doc dd)))
267
268   ;; the BOUNDP test here is to get past cold-init.
269   (when (boundp '*defstruct-hooks*)
270     (dolist (fun *defstruct-hooks*)
271       (funcall fun (find-classoid (dd-name dd)))))
272
273   (/show0 "leaving %TARGET-DEFSTRUCT")
274   (values))
275 \f
276 ;;;; generating out-of-line slot accessor functions
277
278 ;;; FIXME: Ideally, the presence of the type checks in the functions
279 ;;; here would be conditional on the optimization policy at the point
280 ;;; of expansion of DEFSTRUCT. (For now we're just doing the simpler
281 ;;; thing, putting in the type checks unconditionally.)
282
283 ;;; KLUDGE: Why use this closure approach at all?  The macrology in
284 ;;; SLOT-ACCESSOR-FUNS seems to be half stub, half OAOOM to me.  --DFL
285
286 ;;; Return (VALUES SLOT-READER-FUN SLOT-WRITER-FUN).
287 (defun slot-accessor-funs (dd dsd)
288
289   #+sb-xc (/show0 "entering SLOT-ACCESSOR-FUNS")
290
291   ;; various code generators
292   ;;
293   ;; Note: They're only minimally parameterized, and cavalierly grab
294   ;; things like INSTANCE and DSD-INDEX from the namespace they're
295   ;; expanded in.
296   (macrolet (;; code shared between funcallable instance case and the
297              ;; ordinary STRUCTURE-OBJECT case: Handle native
298              ;; structures with LAYOUTs and (possibly) raw slots.
299              (%native-slot-accessor-funs (dd-ref-fun-name)
300                (let ((instance-type-check-form
301                       '(%check-structure-type-from-layout instance layout)))
302                  (/show "macroexpanding %NATIVE-SLOT-ACCESSOR-FUNS" dd-ref-fun-name instance-type-check-form)
303                  `(let ((layout (dd-layout-or-lose dd))
304                         (dsd-raw-type (dsd-raw-type dsd)))
305                     #+sb-xc (/show0 "in %NATIVE-SLOT-ACCESSOR-FUNS macroexpanded code")
306                     ;; Map over all the possible RAW-TYPEs, compiling
307                     ;; a different closure function for each one, so
308                     ;; that once the COND over RAW-TYPEs happens (at
309                     ;; the time closure is allocated) there are no
310                     ;; more decisions to be made and things execute
311                     ;; reasonably efficiently.
312                     (cond
313                      ;; nonraw slot case
314                      ((eql dsd-raw-type t)
315                       #+sb-xc (/show0 "in nonraw slot case")
316                       (%slotplace-accessor-funs
317                        (,dd-ref-fun-name instance dsd-index)
318                        ,instance-type-check-form))
319                      ;; raw slot cases
320                      ,@(mapcar (lambda (rtd)
321                                  (let ((raw-type (raw-slot-data-raw-type rtd))
322                                        (accessor-name
323                                         (raw-slot-data-accessor-name rtd)))
324                                    `((equal dsd-raw-type ',raw-type)
325                                      #+sb-xc (/show0 "in raw slot case")
326                                      (%slotplace-accessor-funs
327                                       (,accessor-name instance dsd-index)
328                                       ,instance-type-check-form))))
329                                *raw-slot-data-list*)
330                      ;; oops
331                      (t
332                       (bug "unexpected DSD-RAW-TYPE ~S" dsd-raw-type))))))
333              ;; code shared between DEFSTRUCT :TYPE LIST and
334              ;; DEFSTRUCT :TYPE VECTOR cases: Handle the "typed
335              ;; structure" case, with no LAYOUTs and no raw slots.
336              (%colontyped-slot-accessor-funs () (error "stub"))
337              ;; the common structure of the raw-slot and not-raw-slot
338              ;; cases, defined in terms of the writable SLOTPLACE. All
339              ;; possible flavors of slot access should be able to pass
340              ;; through here.
341              (%slotplace-accessor-funs (slotplace instance-type-check-form)
342                (/show "macroexpanding %SLOTPLACE-ACCESSOR-FUNS" slotplace instance-type-check-form)
343                `(let ((typecheckfun (typespec-typecheckfun dsd-type)))
344                   (values (if (dsd-safe-p dsd)
345                               (lambda (instance)
346                                 (/noshow0 "in %SLOTPLACE-ACCESSOR-FUNS-defined reader")
347                                 ,instance-type-check-form
348                                 (/noshow0 "back from INSTANCE-TYPE-CHECK-FORM")
349                                 ,slotplace)
350                               (lambda (instance)
351                                 (/noshow0 "in %SLOTPLACE-ACCESSOR-FUNS-defined reader")
352                                 ,instance-type-check-form
353                                 (/noshow0 "back from INSTANCE-TYPE-CHECK-FORM")
354                                 (let ((value ,slotplace))
355                                   (funcall typecheckfun value)
356                                   value)))
357                           (lambda (new-value instance)
358                             (/noshow0 "in %SLOTPLACE-ACCESSOR-FUNS-defined writer")
359                             ,instance-type-check-form
360                             (/noshow0 "back from INSTANCE-TYPE-CHECK-FORM")
361                             (funcall typecheckfun new-value)
362                             (/noshow0 "back from TYPECHECKFUN")
363                             (setf ,slotplace new-value))))))
364
365     (let ((dsd-index (dsd-index dsd))
366           (dsd-type (dsd-type dsd)))
367
368       #+sb-xc (/show0 "got DSD-TYPE=..")
369       #+sb-xc (/hexstr dsd-type)
370       (ecase (dd-type dd)
371
372         ;; native structures
373         (structure
374          #+sb-xc (/show0 "case of DSD-TYPE = STRUCTURE")
375          (%native-slot-accessor-funs %instance-ref))
376
377         ;; structures with the :TYPE option
378
379         ;; FIXME: Worry about these later..
380         #|
381         ;; In :TYPE LIST and :TYPE VECTOR structures, ANSI specifies the
382         ;; layout completely, so that raw slots are impossible.
383         (list
384          (dd-type-slot-accessor-funs nth-but-with-sane-arg-order
385                                  `(%check-structure-type-from-dd
386                                  :maybe-raw-p nil))
387         (vector
388          (dd-type-slot-accessor-funs aref
389                                  :maybe-raw-p nil)))
390         |#
391         ))))
392 \f
393 ;;; Copy any old kind of structure.
394 (defun copy-structure (structure)
395   #!+sb-doc
396   "Return a copy of STRUCTURE with the same (EQL) slot values."
397   (declare (type structure-object structure))
398   (let* ((len (%instance-length structure))
399          (res (%make-instance len))
400          (layout (%instance-layout structure))
401          (nuntagged (layout-n-untagged-slots layout)))
402
403     (declare (type index len))
404     (when (layout-invalid layout)
405       (error "attempt to copy an obsolete structure:~%  ~S" structure))
406
407     ;; Copy ordinary slots.
408     (dotimes (i (- len nuntagged))
409       (declare (type index i))
410       (setf (%instance-ref res i)
411             (%instance-ref structure i)))
412
413     ;; Copy raw slots.
414     (dotimes (i nuntagged)
415       (declare (type index i))
416       (setf (%raw-instance-ref/word res i)
417             (%raw-instance-ref/word structure i)))
418
419     res))
420
421 \f
422
423 ;; Do an EQUALP comparison on the raw slots (only, not the normal slots) of a
424 ;; structure.
425 (defun raw-instance-slots-equalp (layout x y)
426   ;; This implementation sucks, but hopefully EQUALP on raw structures
427   ;; won't be a major bottleneck for anyone. It'd be tempting to do
428   ;; all this with %RAW-INSTANCE-REF/WORD and bitwise comparisons, but
429   ;; that'll fail in some cases. For example -0.0 and 0.0 are EQUALP
430   ;; but have different bit patterns. -- JES, 2007-08-21
431   (loop with i = -1
432         for dsd in (dd-slots (layout-info layout))
433         for raw-type = (dsd-raw-type dsd)
434         for rsd = (when raw-type
435                     (find raw-type
436                           *raw-slot-data-list*
437                           :key 'raw-slot-data-raw-type))
438         for accessor = (when rsd
439                          (raw-slot-data-accessor-name rsd))
440         always (or (not accessor)
441                    (progn
442                      (incf i)
443                      (equalp (funcall accessor x i)
444                              (funcall accessor y i))))))
445 \f
446 ;;; default PRINT-OBJECT method
447
448 (defun %print-structure-sans-layout-info (name stream)
449   ;; KLUDGE: during PCL build debugging, we can sometimes
450   ;; attempt to print out a PCL object (with null LAYOUT-INFO).
451   (pprint-logical-block (stream nil :prefix "#<" :suffix ">")
452     (prin1 name stream)
453     (write-char #\space stream)
454     (write-string "(no LAYOUT-INFO)" stream)))
455
456 (defun %print-structure-sans-slots (name stream)
457   ;; the structure type doesn't count as a component for *PRINT-LEVEL*
458   ;; processing. We can likewise elide the logical block processing,
459   ;; since all we have to print is the type name. -- CSR, 2004-10-05
460   (write-string "#S(" stream)
461   (prin1 name stream)
462   (write-char #\) stream))
463
464 (defun %default-structure-pretty-print (structure stream)
465   (let* ((layout (%instance-layout structure))
466          (name (classoid-name (layout-classoid layout)))
467          (dd (layout-info layout)))
468     (cond ((not dd)
469            (%print-structure-sans-layout-info name stream))
470           ((not (dd-slots dd))
471            (%print-structure-sans-slots name stream))
472           (t
473            (pprint-logical-block (stream nil :prefix "#S(" :suffix ")")
474              (prin1 name stream)
475              (let ((remaining-slots (dd-slots dd)))
476                (when remaining-slots
477                  (write-char #\space stream)
478                  ;; CMU CL had (PPRINT-INDENT :BLOCK 2 STREAM) here,
479                  ;; but I can't see why. -- WHN 20000205
480                  (pprint-newline :linear stream)
481                  (loop
482                    (pprint-pop)
483                    (let ((slot (pop remaining-slots)))
484                      (write-char #\: stream)
485                      (output-symbol-name (symbol-name (dsd-name slot)) stream)
486                      (write-char #\space stream)
487                      (pprint-newline :miser stream)
488                      (output-object (funcall (fdefinition (dsd-accessor-name slot))
489                                              structure)
490                                     stream)
491                      (when (null remaining-slots)
492                        (return))
493                      (write-char #\space stream)
494                      (pprint-newline :linear stream))))))))))
495
496 (defun %default-structure-ugly-print (structure stream)
497   (let* ((layout (%instance-layout structure))
498          (name (classoid-name (layout-classoid layout)))
499          (dd (layout-info layout)))
500     (cond ((not dd)
501            (%print-structure-sans-layout-info name stream))
502           ((not (dd-slots dd))
503            (%print-structure-sans-slots name stream))
504           (t
505            (descend-into (stream)
506              (write-string "#S(" stream)
507              (prin1 name stream)
508              (do ((index 0 (1+ index))
509                   (remaining-slots (dd-slots dd) (cdr remaining-slots)))
510                  ((or (null remaining-slots)
511                       (and (not *print-readably*)
512                            *print-length*
513                            (>= index *print-length*)))
514                   (if (null remaining-slots)
515                       (write-string ")" stream)
516                       (write-string " ...)" stream)))
517                (declare (type index index))
518                (write-string " :" stream)
519                (let ((slot (first remaining-slots)))
520                  (output-symbol-name (symbol-name (dsd-name slot)) stream)
521                  (write-char #\space stream)
522                  (output-object
523                   (funcall (fdefinition (dsd-accessor-name slot))
524                            structure)
525                   stream))))))))
526
527 (defun default-structure-print (structure stream depth)
528   (declare (ignore depth))
529   (cond ((funcallable-instance-p structure)
530          (print-unreadable-object (structure stream :identity t :type t)))
531         (*print-pretty*
532          (%default-structure-pretty-print structure stream))
533         (t
534          (%default-structure-ugly-print structure stream))))
535
536 (def!method print-object ((x structure-object) stream)
537   (default-structure-print x stream *current-level-in-print*))
538 \f
539 ;;;; testing structure types
540
541 ;;; Return true if OBJ is an object of the structure type
542 ;;; corresponding to LAYOUT. This is called by the accessor closures,
543 ;;; which have a handle on the type's LAYOUT.
544 ;;;
545 ;;; FIXME: This is fairly big, so it should probably become
546 ;;; MAYBE-INLINE instead of INLINE, or its inlineness should become
547 ;;; conditional (probably through DEFTRANSFORM) on (> SPEED SPACE). Or
548 ;;; else we could fix things up so that the things which call it are
549 ;;; all closures, so that it's expanded only in a small number of
550 ;;; places.
551 #!-sb-fluid (declaim (inline typep-to-layout))
552 (defun typep-to-layout (obj layout)
553   (declare (type layout layout) (optimize (speed 3) (safety 0)))
554   (/noshow0 "entering TYPEP-TO-LAYOUT, OBJ,LAYOUT=..")
555   (/nohexstr obj)
556   (/nohexstr layout)
557   (when (layout-invalid layout)
558     (error "An obsolete structure accessor function was called."))
559   (/noshow0 "back from testing LAYOUT-INVALID LAYOUT")
560   (and (%instancep obj)
561        (let ((obj-layout (%instance-layout obj)))
562          (cond ((eq obj-layout layout)
563                 ;; (In this case OBJ-LAYOUT can't be invalid, because
564                 ;; we determined LAYOUT is valid in the test above.)
565                 (/noshow0 "EQ case")
566                 t)
567                ((layout-invalid obj-layout)
568                 (/noshow0 "LAYOUT-INVALID case")
569                 (error 'layout-invalid
570                        :expected-type (layout-classoid obj-layout)
571                        :datum obj))
572                (t
573                 (let ((depthoid (layout-depthoid layout)))
574                   (/noshow0 "DEPTHOID case, DEPTHOID,LAYOUT-INHERITS=..")
575                   (/nohexstr depthoid)
576                   (/nohexstr layout-inherits)
577                   (and (> (layout-depthoid obj-layout) depthoid)
578                        (eq (svref (layout-inherits obj-layout) depthoid)
579                            layout))))))))
580 \f
581 ;;;; checking structure types
582
583 ;;; Check that X is an instance of the named structure type.
584 (defmacro %check-structure-type-from-name (x name)
585   `(%check-structure-type-from-layout ,x ,(compiler-layout-or-lose name)))
586
587 ;;; Check that X is a structure of the type described by DD.
588 (defmacro %check-structure-type-from-dd (x dd)
589   (declare (type defstruct-description dd))
590   (let ((class-name (dd-name dd)))
591     (ecase (dd-type dd)
592       ((structure funcallable-instance)
593        `(%check-structure-type-from-layout
594          ,x
595          ,(compiler-layout-or-lose class-name)))
596       ((vector)
597        (with-unique-names (xx)
598          `(let ((,xx ,x))
599             (declare (type vector ,xx))
600             ,@(when (dd-named dd)
601                 `((unless (eql (aref ,xx 0) ',class-name)
602                     (error
603                      'simple-type-error
604                      :datum (aref ,xx 0)
605                      :expected-type `(member ,class-name)
606                      :format-control
607                      "~@<missing name in instance of ~
608                       VECTOR-typed structure ~S: ~2I~_S~:>"
609                      :format-arguments (list ',class-name ,xx)))))
610             (values))))
611       ((list)
612        (with-unique-names (xx)
613          `(let ((,xx ,x))
614             (declare (type list ,xx))
615             ,@(when (dd-named dd)
616                 `((unless (eql (first ,xx) ',class-name)
617                     (error
618                      'simple-type-error
619                      :datum (aref ,xx 0)
620                      :expected-type `(member ,class-name)
621                      :format-control
622                      "~@<missing name in instance of LIST-typed structure ~S: ~
623                       ~2I~_S~:>"
624                      :format-arguments (list ',class-name ,xx)))))
625             (values)))))))
626
627 ;;; Check that X is an instance of the structure class with layout LAYOUT.
628 (defun %check-structure-type-from-layout (x layout)
629   (unless (typep-to-layout x layout)
630     (error 'type-error
631            :datum x
632            :expected-type (classoid-name (layout-classoid layout))))
633   (values))
634
635 \f
636 (/show0 "target-defstruct.lisp end of file")