1.0.46.9: detect invalid use of :PREDICATE with DEFSTRUCT :TYPE
[sbcl.git] / src / code / defstruct.lisp
index 5ba663c..fba213a 100644 (file)
            (error "Class is not a structure class: ~S" name))
           (t res))))
 
+(defun compiler-layout-ready-p (name)
+  (let ((layout (info :type :compiler-layout name)))
+    (and layout (typep (layout-info layout) 'defstruct-description))))
+
+(sb!xc:defmacro %make-structure-instance-macro (dd slot-specs &rest slot-vars)
+  `(truly-the ,(dd-name dd)
+              ,(if (compiler-layout-ready-p (dd-name dd))
+                   `(%make-structure-instance ,dd ,slot-specs ,@slot-vars)
+                   ;; Non-toplevel defstructs don't have a layout at compile time,
+                   ;; so we need to construct the actual function at runtime -- but
+                   ;; we cache it at the call site, so that we don't perform quite
+                   ;; so horribly.
+                   `(let* ((cell (load-time-value (list nil)))
+                           (fun (car cell)))
+                      (if (functionp fun)
+                          (funcall fun ,@slot-vars)
+                          (funcall (setf (car cell)
+                                         (%make-structure-instance-allocator ,dd ,slot-specs))
+                                   ,@slot-vars))))))
+
+(declaim (ftype (sfunction (defstruct-description list) function)
+                %make-structure-instance-allocator))
+(defun %make-structure-instance-allocator (dd slot-specs)
+  (let ((vars (make-gensym-list (length slot-specs))))
+    (values (compile nil `(lambda (,@vars)
+                            (%make-structure-instance-macro ,dd ',slot-specs ,@vars))))))
+
+(defun %make-funcallable-structure-instance-allocator (dd slot-specs)
+  (when slot-specs
+    (bug "funcallable-structure-instance allocation with slots unimplemented"))
+  (let ((name (dd-name dd))
+        (length (dd-length dd))
+        (nobject (gensym "OBJECT")))
+    (values
+     (compile nil `(lambda ()
+                     (let ((,nobject (%make-funcallable-instance ,length)))
+                       (setf (%funcallable-instance-layout ,nobject)
+                             (%delayed-get-compiler-layout ,name))
+                       ,nobject))))))
+
 ;;; Delay looking for compiler-layout until the constructor is being
 ;;; compiled, since it doesn't exist until after the EVAL-WHEN
 ;;; (COMPILE) stuff is compiled. (Or, in the oddball case when
                   (error "Class is not a structure class: ~S" ',name))
                 ,layout))))))
 
-;;; Get layout right away.
-(sb!xc:defmacro compile-time-find-layout (name)
-  (find-layout name))
-
 ;;; re. %DELAYED-GET-COMPILER-LAYOUT and COMPILE-TIME-FIND-LAYOUT, above..
 ;;;
 ;;; FIXME: Perhaps both should be defined with DEFMACRO-MUNDANELY?
     (raw-type (missing-arg) :type (or symbol cons) :read-only t)
     ;; What operator is used to access a slot of this type?
     (accessor-name (missing-arg) :type symbol :read-only t)
+    (init-vop (missing-arg) :type symbol :read-only t)
     ;; How many words are each value of this type?
     (n-words (missing-arg) :type (and index (integer 1)) :read-only t)
     ;; Necessary alignment in units of words.  Note that instances
     (alignment 1 :type (integer 1 2) :read-only t))
 
   (defvar *raw-slot-data-list*
-    #!+hppa
-    nil
-    #!-hppa
     (let ((double-float-alignment
            ;; white list of architectures that can load unaligned doubles:
            #!+(or x86 x86-64 ppc) 1
       (list
        (make-raw-slot-data :raw-type 'sb!vm:word
                            :accessor-name '%raw-instance-ref/word
+                           :init-vop 'sb!vm::raw-instance-init/word
                            :n-words 1)
        (make-raw-slot-data :raw-type 'single-float
                            :accessor-name '%raw-instance-ref/single
+                           :init-vop 'sb!vm::raw-instance-init/single
                            ;; KLUDGE: On 64 bit architectures, we
                            ;; could pack two SINGLE-FLOATs into the
                            ;; same word if raw slots were indexed
                            :n-words 1)
        (make-raw-slot-data :raw-type 'double-float
                            :accessor-name '%raw-instance-ref/double
+                           :init-vop 'sb!vm::raw-instance-init/double
                            :alignment double-float-alignment
                            :n-words (/ 8 sb!vm:n-word-bytes))
        (make-raw-slot-data :raw-type 'complex-single-float
                            :accessor-name '%raw-instance-ref/complex-single
+                           :init-vop 'sb!vm::raw-instance-init/complex-single
                            :n-words (/ 8 sb!vm:n-word-bytes))
        (make-raw-slot-data :raw-type 'complex-double-float
                            :accessor-name '%raw-instance-ref/complex-double
+                           :init-vop 'sb!vm::raw-instance-init/complex-double
                            :alignment double-float-alignment
                            :n-words (/ 16 sb!vm:n-word-bytes))
        #!+long-float
        (make-raw-slot-data :raw-type long-float
                            :accessor-name '%raw-instance-ref/long
+                           :init-vop 'sb!vm::raw-instance-init/long
                            :n-words #!+x86 3 #!+sparc 4)
        #!+long-float
        (make-raw-slot-data :raw-type complex-long-float
                            :accessor-name '%raw-instance-ref/complex-long
+                           :init-vop 'sb!vm::raw-instance-init/complex-long
                            :n-words #!+x86 6 #!+sparc 8)))))
+(defun raw-slot-words (type)
+  (let ((rsd (find type *raw-slot-data-list* :key #'raw-slot-data-raw-type)))
+    (if rsd
+        (raw-slot-data-n-words rsd)
+        (error "Invalid raw slot type: ~S" type))))
 \f
 ;;;; the legendary DEFSTRUCT macro itself (both CL:DEFSTRUCT and its
 ;;;; close personal friend SB!XC:DEFSTRUCT)
         (declare (notinline find-classoid))
         ,@(let ((pf (dd-print-function defstruct))
                 (po (dd-print-object defstruct))
-                (x (gensym))
-                (s (gensym)))
+                (x (sb!xc:gensym "OBJECT"))
+                (s (sb!xc:gensym "STREAM")))
             ;; Giving empty :PRINT-OBJECT or :PRINT-FUNCTION options
             ;; leaves PO or PF equal to NIL. The user-level effect is
             ;; to generate a PRINT-OBJECT method specialized for the type,
               `((setf (structure-classoid-constructor (find-classoid ',name))
                       #',def-con))))))))
 
-;;; shared logic for CL:DEFSTRUCT and SB!XC:DEFSTRUCT
+;;; shared logic for host macroexpansion for SB!XC:DEFSTRUCT and
+;;; cross-compiler macroexpansion for CL:DEFSTRUCT
 (defmacro !expander-for-defstruct (name-and-options
                                    slot-descriptions
                                    expanding-into-code-for-xc-host-p)
                 ;; class.
                 (with-single-package-locked-error
                     (:symbol ',name "defining ~A as a structure"))
-                (%defstruct ',dd ',inherits)
+                (%defstruct ',dd ',inherits (sb!c:source-location))
                 (eval-when (:compile-toplevel :load-toplevel :execute)
                   (%compiler-defstruct ',dd ',inherits))
                 ,@(unless expanding-into-code-for-xc-host-p
                   (:symbol ',name "defining ~A as a structure"))
               (eval-when (:compile-toplevel :load-toplevel :execute)
                 (setf (info :typed-structure :info ',name) ',dd))
+              (eval-when (:load-toplevel :execute)
+                (setf (info :source-location :typed-structure ',name)
+                      (sb!c:source-location)))
               ,@(unless expanding-into-code-for-xc-host-p
                   (append (typed-accessor-definitions dd)
                           (typed-predicate-definitions dd)
                           (typed-copier-definitions dd)
-                          (constructor-definitions dd)))
+                          (constructor-definitions dd)
+                          (when (dd-doc dd)
+                            `((setf (fdocumentation ',(dd-name dd) 'structure)
+                               ',(dd-doc dd))))))
               ',name)))))
 
 (sb!xc:defmacro defstruct (name-and-options &rest slot-descriptions)
           (let ((inherited (accessor-inherited-data name defstruct)))
             (cond
               ((not inherited)
-               (stuff `(declaim (inline ,name (setf ,name))))
+               (stuff `(declaim (inline ,name ,@(unless (dsd-read-only slot)
+                                                        `((setf ,name))))))
                ;; FIXME: The arguments in the next two DEFUNs should
                ;; be gensyms. (Otherwise e.g. if NEW-VALUE happened to
                ;; be the name of a special variable, things could get
 (defun parse-defstruct-name-and-options (name-and-options)
   (destructuring-bind (name &rest options) name-and-options
     (aver name) ; A null name doesn't seem to make sense here.
-    (let ((dd (make-defstruct-description name)))
+    (let ((dd (make-defstruct-description name))
+          (predicate-named-p nil))
       (dolist (option options)
         (cond ((eq option :named)
                (setf (dd-named dd) t))
               ((consp option)
+               (when (and (eq (car option) :predicate) (second option))
+                 (setf predicate-named-p t))
                (parse-1-dd-option option dd))
               ((member option '(:conc-name :constructor :copier :predicate))
                (parse-1-dd-option (list option) dd))
            ;; make that messy, alas.)
            (incf (dd-length dd))))
         (t
+         ;; In case we are here, :TYPE is specified.
+         (when (and predicate-named-p (not (dd-named dd)))
+           (error ":PREDICATE cannot be used with :TYPE unless :NAMED is also specified."))
          (require-no-print-options-so-far dd)
          (when (dd-named dd)
            (incf (dd-length dd)))
       ;;x#-sb-xc-host
       ;;x(when (and (fboundp accessor-name)
       ;;x           (not (accessor-inherited-data accessor-name defstruct)))
-      ;;x  (style-warn "redefining ~S in DEFSTRUCT" accessor-name)))
+      ;;x  (style-warn "redefining ~/sb-impl::print-symbol-with-prefix/ ~
+      ;;                in DEFSTRUCT" accessor-name)))
       ;; which was done until sbcl-0.8.11.18 or so, is wrong: it causes
       ;; a warning at MACROEXPAND time, when instead the warning should
       ;; occur not just because the code was constructed, but because it
 ;;; incompatible redefinition. Define those functions which are
 ;;; sufficiently stereotyped that we can implement them as standard
 ;;; closures.
-(defun %defstruct (dd inherits)
+(defun %defstruct (dd inherits source-location)
   (declare (type defstruct-description dd))
 
   ;; We set up LAYOUTs even in the cross-compilation host.
            (unless (eq (classoid-layout classoid) layout)
              (register-layout layout)))
           (t
+           (%redefine-defstruct classoid old-layout layout)
            (let ((old-dd (layout-info old-layout)))
              (when (defstruct-description-p old-dd)
                (dolist (slot (dd-slots old-dd))
                  (fmakunbound (dsd-accessor-name slot))
                  (unless (dsd-read-only slot)
                    (fmakunbound `(setf ,(dsd-accessor-name slot)))))))
-           (%redefine-defstruct classoid old-layout layout)
            (setq layout (classoid-layout classoid))))
     (setf (find-classoid (dd-name dd)) classoid)
 
+    (sb!c:with-source-location (source-location)
+      (setf (layout-source-location layout) source-location))
+
     ;; Various other operations only make sense on the target SBCL.
     #-sb-xc-host
     (%target-defstruct dd layout))
 
 ;;; Return a LAMBDA form which can be used to set a slot.
 (defun slot-setter-lambda-form (dd dsd)
-  `(lambda (new-value instance)
-     ,(funcall (nth-value 1 (slot-accessor-transforms dd dsd))
-               '(dummy new-value instance))))
+  ;; KLUDGE: Evaluating the results of SLOT-ACCESSOR-TRANSFORMS needs
+  ;; a lexenv.
+  (let ((sb!c:*lexenv* (if (boundp 'sb!c:*lexenv*)
+                           sb!c:*lexenv*
+                           (sb!c::make-null-lexenv))))
+    `(lambda (new-value instance)
+       ,(funcall (nth-value 1 (slot-accessor-transforms dd dsd))
+                 '(dummy new-value instance)))))
+
+;;; Blow away all the compiler info for the structure CLASS. Iterate
+;;; over this type, clearing the compiler structure type info, and
+;;; undefining all the associated functions.  If SUBCLASSES-P, also do
+;;; the same for subclasses.  FIXME: maybe rename UNDEFINE-FUN-NAME to
+;;; UNDECLARE-FUNCTION-NAME?
+(defun undeclare-structure (classoid subclasses-p)
+  (let ((info (layout-info (classoid-layout classoid))))
+    (when (defstruct-description-p info)
+      (let ((type (dd-name info)))
+        (remhash type *typecheckfuns*)
+        (setf (info :type :compiler-layout type) nil)
+        (undefine-fun-name (dd-copier-name info))
+        (undefine-fun-name (dd-predicate-name info))
+        (dolist (slot (dd-slots info))
+          (let ((fun (dsd-accessor-name slot)))
+            (unless (accessor-inherited-data fun info)
+              (undefine-fun-name fun)
+              (unless (dsd-read-only slot)
+                (undefine-fun-name `(setf ,fun)))))))
+      ;; Clear out the SPECIFIER-TYPE cache so that subsequent
+      ;; references are unknown types.
+      (values-specifier-type-cache-clear)))
+  (when subclasses-p
+    (let ((subclasses (classoid-subclasses classoid)))
+      (when subclasses
+        (collect ((subs))
+          (dohash ((classoid layout)
+                   subclasses
+                   :locked t)
+            (declare (ignore layout))
+            (undeclare-structure classoid nil)
+            (subs (classoid-proper-name classoid)))
+          ;; Is it really necessary to warn about
+          ;; undeclaring functions for subclasses?
+          (when (subs)
+            (warn "undeclaring functions for old subclasses ~
+                               of ~S:~%  ~S"
+                  (classoid-name classoid)
+                  (subs))))))))
 
 ;;; core compile-time setup of any class with a LAYOUT, used even by
 ;;; !DEFSTRUCT-WITH-ALTERNATE-METACLASS weirdosities
           (info :type :compiler-layout (dd-name dd))
         (ensure-structure-class dd
                                 inherits
-                                (if clayout-p "previously compiled" "current")
-                                "compiled"
+                                (if clayout-p
+                                    "The most recently compiled"
+                                    "The current")
+                                "the most recently loaded"
                                 :compiler-layout clayout))
     (cond (old-layout
-           (undefine-structure (layout-classoid old-layout))
-           (when (and (classoid-subclasses classoid)
-                      (not (eq layout old-layout)))
-             (collect ((subs))
-                      (dohash (classoid layout (classoid-subclasses classoid))
-                        (declare (ignore layout))
-                        (undefine-structure classoid)
-                        (subs (classoid-proper-name classoid)))
-                      (when (subs)
-                        (warn "removing old subclasses of ~S:~%  ~S"
-                              (classoid-name classoid)
-                              (subs))))))
+           (undeclare-structure (layout-classoid old-layout)
+                                (and (classoid-subclasses classoid)
+                                     (not (eq layout old-layout))))
+           (setf (layout-invalid layout) nil)
+           ;; FIXME: it might be polite to hold onto old-layout and
+           ;; restore it at the end of the file.  -- RMK 2008-09-19
+           ;; (International Talk Like a Pirate Day).
+           (warn "~@<Clobbering the compiler's idea of the layout of ~A.~:@>"
+                 classoid))
           (t
            (unless (eq (classoid-layout classoid) layout)
              (register-layout layout :invalidate nil))
       (let* ((accessor-name (dsd-accessor-name dsd))
              (dsd-type (dsd-type dsd)))
         (when accessor-name
+          (setf (info :function :structure-accessor accessor-name) dd)
           (let ((inherited (accessor-inherited-data accessor-name dd)))
             (cond
               ((not inherited)
                         :destruct-layout old-layout))))
   (values))
 
+(declaim (inline dd-layout-length))
+(defun dd-layout-length (dd)
+  (+ (dd-length dd) (dd-raw-length dd)))
+
+(declaim (ftype (sfunction (defstruct-description) index) dd-instance-length))
+(defun dd-instance-length (dd)
+  ;; Make sure the object ends at a two-word boundary.  Note that this does
+  ;; not affect the amount of memory used, since the allocator would add the
+  ;; same padding anyway.  However, raw slots are indexed from the length of
+  ;; the object as indicated in the header, so the pad word needs to be
+  ;; included in that length to guarantee proper alignment of raw double float
+  ;; slots, necessary for (at least) the SPARC backend.
+  (let ((layout-length (dd-layout-length dd)))
+    (declare (type index layout-length))
+    (+ layout-length (mod (1+ layout-length) 2))))
+
 ;;; This is called when we are about to define a structure class. It
 ;;; returns a (possibly new) class object and the layout which should
 ;;; be used for the new definition (may be the current layout, and
                                    (lambda (x)
                                      (sb!xc:typep x 'structure-classoid))
                                    (lambda (x)
-                                     (sb!xc:typep x (find-classoid class))))
+                                     (sb!xc:typep x (classoid-name (find-classoid class)))))
                                (fdefinition constructor)))
     (setf (classoid-direct-superclasses class)
           (case (dd-name info)
     (let ((new-layout (make-layout :classoid class
                                    :inherits inherits
                                    :depthoid (length inherits)
-                                   :length (+ (dd-length info)
-                                              (dd-raw-length info))
+                                   :length (dd-layout-length info)
                                    :n-untagged-slots (dd-raw-length info)
                                    :info info))
           (old-layout (or compiler-layout old-layout)))
              (error "shouldn't happen! strange thing in LAYOUT-INFO:~%  ~S"
                     old-layout)
              (values class new-layout old-layout)))))))))
-
-;;; Blow away all the compiler info for the structure CLASS. Iterate
-;;; over this type, clearing the compiler structure type info, and
-;;; undefining all the associated functions.
-(defun undefine-structure (class)
-  (let ((info (layout-info (classoid-layout class))))
-    (when (defstruct-description-p info)
-      (let ((type (dd-name info)))
-        (remhash type *typecheckfuns*)
-        (setf (info :type :compiler-layout type) nil)
-        (undefine-fun-name (dd-copier-name info))
-        (undefine-fun-name (dd-predicate-name info))
-        (dolist (slot (dd-slots info))
-          (let ((fun (dsd-accessor-name slot)))
-            (unless (accessor-inherited-data fun info)
-              (undefine-fun-name fun)
-              (unless (dsd-read-only slot)
-                (undefine-fun-name `(setf ,fun)))))))
-      ;; Clear out the SPECIFIER-TYPE cache so that subsequent
-      ;; references are unknown types.
-      (values-specifier-type-cache-clear)))
-  (values))
 \f
 ;;; Return a list of pairs (name . index). Used for :TYPE'd
 ;;; constructors to find all the names that we have to splice in &
     (loop for dsd in (dd-slots dd) and val in values do
       (setf (elt vals (dsd-index dsd))
             (if (eq val '.do-not-initialize-slot.) 0 val)))
-
     `(defun ,cons-name ,arglist
        (declare ,@(mapcar (lambda (var type) `(type ,type ,var)) vars types))
        (list ,@vals))))
 (defun create-structure-constructor (dd cons-name arglist vars types values)
-  (let* ((instance (gensym "INSTANCE")))
+  ;; The difference between the two implementations here is that on all
+  ;; platforms we don't have the appropriate RAW-INSTANCE-INIT VOPS, which
+  ;; must be able to deal with immediate values as well -- unlike
+  ;; RAW-INSTANCE-SET VOPs, which never end up seeing immediate values. With
+  ;; some additional cleverness we might manage without them and just a single
+  ;; implementation here, though -- figure out a way to ensure that on those
+  ;; platforms we always still get a non-immediate TN in every case...
+  ;;
+  ;; Until someone does that, this means that instances with raw slots can be
+  ;; DX allocated only on platforms with those additional VOPs.
+  #!+raw-instance-init-vops
+  (let* ((slot-values nil)
+         (slot-specs
+          (mapcan (lambda (dsd value)
+                    (unless (eq value '.do-not-initialize-slot.)
+                      (push value slot-values)
+                      (list (list* :slot (dsd-raw-type dsd) (dsd-index dsd)))))
+                  (dd-slots dd)
+                  values)))
     `(defun ,cons-name ,arglist
-       (declare ,@(mapcar (lambda (var type) `(type ,type ,var))
-                          vars types))
-       (let ((,instance (truly-the ,(dd-name dd)
-                          (%make-instance-with-layout
-                           (%delayed-get-compiler-layout ,(dd-name dd))))))
-         ,@(mapcar (lambda (dsd value)
-                     ;; (Note that we can't in general use the
-                     ;; ordinary named slot setter function here
-                     ;; because the slot might be :READ-ONLY, so we
-                     ;; whip up new LAMBDA representations of slot
-                     ;; setters for the occasion.)
-                     (unless (eq value '.do-not-initialize-slot.)
-                       `(,(slot-setter-lambda-form dd dsd) ,value ,instance)))
-                   (dd-slots dd)
-                   values)
-         ,instance))))
+       (declare ,@(mapcar (lambda (var type) `(type ,type ,var)) vars types))
+       (%make-structure-instance-macro ,dd ',slot-specs ,@(reverse slot-values))))
+  #!-raw-instance-init-vops
+  (let ((instance (gensym "INSTANCE")) slot-values slot-specs raw-slots raw-values)
+    (mapc (lambda (dsd value)
+            (unless (eq value '.do-not-initialize-slot.)
+              (let ((raw-type (dsd-raw-type dsd)))
+                (cond ((eq t raw-type)
+                       (push value slot-values)
+                       (push (list* :slot raw-type (dsd-index dsd)) slot-specs))
+                      (t
+                       (push value raw-values)
+                       (push dsd raw-slots))))))
+          (dd-slots dd)
+          values)
+    `(defun ,cons-name ,arglist
+       (declare ,@(mapcar (lambda (var type) `(type ,type ,var)) vars types))
+       ,(if raw-slots
+            `(let ((,instance (%make-structure-instance-macro ,dd ',slot-specs ,@slot-values)))
+              ,@(mapcar (lambda (dsd value)
+                          ;; (Note that we can't in general use the
+                          ;; ordinary named slot setter function here
+                          ;; because the slot might be :READ-ONLY, so we
+                          ;; whip up new LAMBDA representations of slot
+                          ;; setters for the occasion.)
+                          `(,(slot-setter-lambda-form dd dsd) ,value ,instance))
+                        raw-slots
+                        raw-values)
+              ,instance)
+            `(%make-structure-instance-macro ,dd ',slot-specs ,@slot-values)))))
 
 ;;; Create a default (non-BOA) keyword constructor.
 (defun create-keyword-constructor (defstruct creator)
             (types)
             (vals))
     (dolist (slot (dd-slots defstruct))
-      (let ((dum (gensym))
+      (let ((dum (sb!xc:gensym "DUM"))
             (name (dsd-name slot)))
         (arglist `((,(keywordicate name) ,dum) ,(dsd-default slot)))
         (types (dsd-type slot))
         (when auxp
           (arglist '&aux)
           (dolist (arg aux)
-            (arglist arg)
             (if (proper-list-of-length-p arg 2)
-              (let ((var (first arg)))
-                (vars var)
-                (types (get-slot var)))
-              (skipped-vars (if (consp arg) (first arg) arg))))))
+                (let ((var (first arg)))
+                  (arglist arg)
+                  (vars var)
+                  (types (get-slot var)))
+                (skipped-vars (if (consp arg) (first arg) arg))))))
 
       (funcall creator defstruct (first boa)
                (arglist) (vars) (types)
                (loop for slot in (dd-slots defstruct)
                      for name = (dsd-name slot)
                      collect (cond ((find name (skipped-vars) :test #'string=)
+                                    ;; CLHS 3.4.6 Boa Lambda Lists
                                     (setf (dsd-safe-p slot) nil)
                                     '.do-not-initialize-slot.)
                                    ((or (find (dsd-name slot) (vars) :test #'string=)
-                                        (dsd-default slot)))))))))
+                                        (let ((type (dsd-type slot)))
+                                          (if (eq t type)
+                                              (dsd-default slot)
+                                              `(the ,type ,(dsd-default slot))))))))))))
 
 ;;; Grovel the constructor options, and decide what constructors (if
 ;;; any) to create.
           (dd-type dd) dd-type)
     dd))
 
+;;; make !DEFSTRUCT-WITH-ALTERNATE-METACLASS compilable by the host
+;;; lisp, installing the information we need to reason about the
+;;; structures (layouts and classoids).
+;;;
+;;; FIXME: we should share the parsing and the DD construction between
+;;; this and the cross-compiler version, but my brain was too small to
+;;; get that right.  -- CSR, 2006-09-14
+#+sb-xc-host
+(defmacro !defstruct-with-alternate-metaclass
+    (class-name &key
+                (slot-names (missing-arg))
+                (boa-constructor (missing-arg))
+                (superclass-name (missing-arg))
+                (metaclass-name (missing-arg))
+                (metaclass-constructor (missing-arg))
+                (dd-type (missing-arg))
+                predicate
+                (runtime-type-checks-p t))
+
+  (declare (type (and list (not null)) slot-names))
+  (declare (type (and symbol (not null))
+                 boa-constructor
+                 superclass-name
+                 metaclass-name
+                 metaclass-constructor))
+  (declare (type symbol predicate))
+  (declare (type (member structure funcallable-structure) dd-type))
+  (declare (ignore boa-constructor predicate runtime-type-checks-p))
+
+  (let* ((dd (make-dd-with-alternate-metaclass
+              :class-name class-name
+              :slot-names slot-names
+              :superclass-name superclass-name
+              :metaclass-name metaclass-name
+              :metaclass-constructor metaclass-constructor
+              :dd-type dd-type)))
+    `(progn
+
+      (eval-when (:compile-toplevel :load-toplevel :execute)
+        (%compiler-set-up-layout ',dd ',(inherits-for-structure dd))))))
+
+(sb!xc:proclaim '(special *defstruct-hooks*))
+
 (sb!xc:defmacro !defstruct-with-alternate-metaclass
     (class-name &key
                 (slot-names (missing-arg))
               :dd-type dd-type))
          (dd-slots (dd-slots dd))
          (dd-length (1+ (length slot-names)))
-         (object-gensym (gensym "OBJECT"))
-         (new-value-gensym (gensym "NEW-VALUE-"))
+         (object-gensym (sb!xc:gensym "OBJECT"))
+         (new-value-gensym (sb!xc:gensym "NEW-VALUE-"))
          (delayed-layout-form `(%delayed-get-compiler-layout ,class-name)))
     (multiple-value-bind (raw-maker-form raw-reffer-operator)
         (ecase dd-type
           (structure
-           (values `(let ((,object-gensym (%make-instance ,dd-length)))
-                      (setf (%instance-layout ,object-gensym)
-                            ,delayed-layout-form)
-                      ,object-gensym)
+           (values `(%make-structure-instance-macro ,dd nil)
                    '%instance-ref))
           (funcallable-structure
            (values `(let ((,object-gensym
              ;; code, which knows how to generate inline type tests
              ;; for the whole CMU CL INSTANCE menagerie.
              `(defun ,predicate (,object-gensym)
-                (typep ,object-gensym ',class-name)))))))
+                (typep ,object-gensym ',class-name)))
+
+         (when (boundp '*defstruct-hooks*)
+           (dolist (fun *defstruct-hooks*)
+             (funcall fun (find-classoid ',(dd-name dd)))))))))
 \f
 ;;;; finalizing bootstrapping
 
          (inherits (inherits-for-structure dd)))
     (%compiler-defstruct dd inherits)))
 
+;;; finding these beasts
+(defun find-defstruct-description (name &optional (errorp t))
+  (let ((info (layout-info (classoid-layout (find-classoid name errorp)))))
+    (if (defstruct-description-p info)
+        info
+        (when errorp
+          (error "No DEFSTRUCT-DESCRIPTION for ~S." name)))))
+
 (/show0 "code/defstruct.lisp end of file")