0.pre7.35:
[sbcl.git] / src / code / defstruct.lisp
index 2f86b39..f00df2f 100644 (file)
@@ -11,6 +11,8 @@
 ;;;; files for more information.
 
 (in-package "SB!KERNEL")
+
+(/show0 "code/defstruct.lisp 15")
 \f
 ;;;; getting LAYOUTs
 
   ;; documentation on the structure
   (doc nil :type (or string null))
   ;; prefix for slot names. If NIL, none.
-  (conc-name (concat-pnames name '-) :type (or symbol null))
+  (conc-name (symbolicate name "-") :type (or symbol null))
   ;; the name of the primary standard keyword constructor, or NIL if none
   (default-constructor nil :type (or symbol null))
   ;; all the explicit :CONSTRUCTOR specs, with name defaulted
   (constructors () :type list)
   ;; name of copying function
-  (copier (concat-pnames 'copy- name) :type (or symbol null))
+  (copier (symbolicate "COPY-" name) :type (or symbol null))
   ;; name of type predicate
-  (predicate (concat-pnames name '-p) :type (or symbol null))
+  (predicate-name (symbolicate name "-P") :type (or symbol null))
   ;; the arguments to the :INCLUDE option, or NIL if no included
   ;; structure
   (include nil :type list)
@@ -83,7 +85,7 @@
   ;; classes, CLASS-STRUCTURE-P = NIL)
   ;;
   ;; vector element type
-  (element-type 't)
+  (element-type t)
   ;; T if :NAMED was explicitly specified, NIL otherwise
   (named nil :type boolean)
   ;; any INITIAL-OFFSET option on this direct type
   %name        
   ;; its position in the implementation sequence
   (index (required-argument) :type fixnum)
-  ;; Name of accessor, or NIL if this accessor has the same name as an
-  ;; inherited accessor (which we don't want to shadow.)
-  (accessor nil)
+  ;; the name of the accessor function
+  ;;
+  ;; (CMU CL had extra complexity here ("..or NIL if this accessor has
+  ;; the same name as an inherited accessor (which we don't want to
+  ;; shadow)") but that behavior doesn't seem to be specified by (or
+  ;; even particularly consistent with) ANSI, so it's gone in SBCL.)
+  (accessor-name nil)
   default                      ; default value expression
   (type t)                     ; declared type specifier
   ;; If this object does not describe a raw slot, this value is T.
 ;;; string to avoid creating lots of worthless symbols at load time.
 (defun dsd-name (dsd)
   (intern (string (dsd-%name dsd))
-         (if (dsd-accessor dsd)
-             (symbol-package (dsd-accessor dsd))
-             *package*)))
+         (if (dsd-accessor-name dsd)
+             (symbol-package (dsd-accessor-name dsd))
+             (sane-package))))
 \f
 ;;;; typed (non-class) structures
 
 ;;;; the legendary DEFSTRUCT macro itself (both CL:DEFSTRUCT and its
 ;;;; close personal friend SB!XC:DEFSTRUCT)
 
-;;; Return a list of forms to install print and make-load-form funs, mentioning
-;;; them in the expansion so that they can be compiled.
+;;; Return a list of forms to install PRINT and MAKE-LOAD-FORM funs,
+;;; mentioning them in the expansion so that they can be compiled.
 (defun class-method-definitions (defstruct)
   (let ((name (dd-name defstruct)))
     `((locally
                         (funcall #',(farg po) ,x ,s))))
                    (t nil))))
        ,@(let ((pure (dd-pure defstruct)))
-           (cond ((eq pure 't)
+           (cond ((eq pure t)
                   `((setf (layout-pure (class-layout
                                         (sb!xc:find-class ',name)))
                           t)))
        ,@(let ((def-con (dd-default-constructor defstruct)))
            (when (and def-con (not (dd-alternate-metaclass defstruct)))
              `((setf (structure-class-constructor (sb!xc:find-class ',name))
-                     #',def-con))))
-       ;; FIXME: MAKE-LOAD-FORM is supposed to be handled here, too.
-       ))))
+                     #',def-con))))))))
 ;;; FIXME: I really would like to make structure accessors less special,
 ;;; just ordinary inline functions. (Or perhaps inline functions with special
 ;;; compact implementations of their expansions, to avoid bloating the system.)
        (if (class-structure-p dd)
           (let ((inherits (inherits-for-structure dd)))
             `(progn
+               (/noshow0 "doing CLASS-STRUCTURE-P case for DEFSTRUCT " ,name)
                (eval-when (:compile-toplevel :load-toplevel :execute)
                  (%compiler-only-defstruct ',dd ',inherits))
                (%defstruct ',dd ',inherits)
                ,@(when (eq (dd-type dd) 'structure)
                    `((%compiler-defstruct ',dd)))
+               (/noshow0 "starting not-for-the-xc-host section in DEFSTRUCT")
                ,@(unless expanding-into-code-for-xc-host-p
                    (append (raw-accessor-definitions dd)
                            (predicate-definitions dd)
                                        ;(copier-definition dd)
                            (constructor-definitions dd)
                            (class-method-definitions dd)))
+               (/noshow0 "done with DEFSTRUCT " ,name)
                ',name))
           `(progn
+             (/show0 "doing NOT CLASS-STRUCTURE-P case for DEFSTRUCT " ,name)
              (eval-when (:compile-toplevel :load-toplevel :execute)
                (setf (info :typed-structure :info ',name) ',dd))
              ,@(unless expanding-into-code-for-xc-host-p
                          (typed-predicate-definitions dd)
                          (typed-copier-definitions dd)
                          (constructor-definitions dd)))
+             (/noshow0 "done with DEFSTRUCT " ,name)
              ',name)))))
 
 (sb!xc:defmacro defstruct (name-and-options &rest slot-descriptions)
   #!+sb-doc
   "DEFSTRUCT {Name | (Name Option*)} {Slot | (Slot [Default] {Key Value}*)}
-   Define the structure type Name. Instances are created by MAKE-<name>, which
-   takes keyword arguments allowing initial slot values to the specified.
+   Define the structure type Name. Instances are created by MAKE-<name>, 
+   which takes &KEY arguments allowing initial slot values to the specified.
    A SETF'able function <name>-<slot> is defined for each slot to read and
    write slot values. <name>-p is a type predicate.
 
     (collect ((res))
       (dolist (slot (dd-slots dd))
        (let ((stype (dsd-type slot))
-             (accname (dsd-accessor slot))
+             (accessor-name (dsd-accessor-name slot))
              (argname (gensym "ARG"))
              (nvname (gensym "NEW-VALUE-")))
          (multiple-value-bind (accessor offset data)
              (slot-accessor-form dd slot argname)
            ;; When accessor exists and is raw
-           (when (and accname (not (eq accessor '%instance-ref)))
-             (res `(declaim (inline ,accname)))
-             (res `(declaim (ftype (function (,name) ,stype) ,accname)))
-             (res `(defun ,accname (,argname)
+           (when (and accessor-name
+                      (not (eq accessor-name '%instance-ref)))
+             (res `(declaim (inline ,accessor-name)))
+             (res `(declaim (ftype (function (,name) ,stype) ,accessor-name)))
+             (res `(defun ,accessor-name (,argname)
                      (truly-the ,stype (,accessor ,data ,offset))))
              (unless (dsd-read-only slot)
-               (res `(declaim (inline (setf ,accname))))
+               (res `(declaim (inline (setf ,accessor-name))))
                (res `(declaim (ftype (function (,stype ,name) ,stype)
-                                     (setf ,accname))))
+                                     (setf ,accessor-name))))
                ;; FIXME: I rewrote this somewhat from the CMU CL definition.
                ;; Do some basic tests to make sure that reading and writing
                ;; raw slots still works correctly.
-               (res `(defun (setf ,accname) (,nvname ,argname)
+               (res `(defun (setf ,accessor-name) (,nvname ,argname)
                        (setf (,accessor ,data ,offset) ,nvname)
                        ,nvname)))))))
       (res))))
 
 ;;; Return a list of forms which create a predicate for an untyped DEFSTRUCT.
 (defun predicate-definitions (dd)
-  (let ((pred (dd-predicate dd))
+  (let ((pred (dd-predicate-name dd))
        (argname (gensym)))
     (when pred
       (if (eq (dd-type dd) 'funcallable-structure)
 ;;; DEFSTRUCT.
 (defun typed-predicate-definitions (defstruct)
   (let ((name (dd-name defstruct))
-       (pred (dd-predicate defstruct))
+       (predicate-name (dd-predicate-name defstruct))
        (argname (gensym)))
-    (when (and pred (dd-named defstruct))
+    (when (and predicate-name (dd-named defstruct))
       (let ((ltype (dd-lisp-type defstruct)))
-       `((defun ,pred (,argname)
+       `((defun ,predicate-name (,argname)
            (and (typep ,argname ',ltype)
                 (eq (elt (the ,ltype ,argname)
                          ,(cdr (car (last (find-name-indices defstruct)))))
                   conc-name
                   (make-symbol (string conc-name))))))
       (:constructor
-       (destructuring-bind (&optional (cname (concat-pnames 'make- name))
+       (destructuring-bind (&optional (cname (symbolicate "MAKE-" name))
                                      &rest stuff)
           args
         (push (cons cname stuff) (dd-constructors defstruct))))
       (:copier
-       (destructuring-bind (&optional (copier (concat-pnames 'copy- name)))
+       (destructuring-bind (&optional (copier (symbolicate "COPY-" name)))
           args
         (setf (dd-copier defstruct) copier)))
       (:predicate
-       (destructuring-bind (&optional (pred (concat-pnames name '-p))) args
-        (setf (dd-predicate defstruct) pred)))
+       (destructuring-bind (&optional (predicate-name (symbolicate name "-P")))
+          args
+        (setf (dd-predicate-name defstruct) predicate-name)))
       (:include
        (when (dd-include defstruct)
         (error "more than one :INCLUDE option"))
         (cond ((eq type 'funcallable-structure)
                (setf (dd-type defstruct) type))
               ((member type '(list vector))
-               (setf (dd-element-type defstruct) 't)
+               (setf (dd-element-type defstruct) t)
                (setf (dd-type defstruct) type))
               ((and (consp type) (eq (first type) 'vector))
                (destructuring-bind (vector vtype) type
 (eval-when (:compile-toplevel :load-toplevel :execute)
 (defun parse-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 ((defstruct (make-defstruct-description name)))
       (dolist (option options)
        (cond ((consp option)
                                          name-and-options))))
     (when (stringp (car slot-descriptions))
       (setf (dd-doc result) (pop slot-descriptions)))
-    (dolist (slot slot-descriptions)
-      (allocate-1-slot result (parse-1-dsd result slot)))
+    (dolist (slot-description slot-descriptions)
+      (allocate-1-slot result (parse-1-dsd result slot-description)))
     result))
 
 ) ; EVAL-WHEN
 ;;;; stuff to parse slot descriptions
 
 ;;; Parse a slot description for DEFSTRUCT, add it to the description
-;;; and return it. If supplied, ISLOT is a pre-initialized DSD that we
-;;; modify to get the new slot. This is supplied when handling
-;;; included slots. If the new accessor name is already an accessor
-;;; for same slot in some included structure, then set the
-;;; DSD-ACCESSOR to NIL so that we don't clobber the more general
-;;; accessor.
+;;; and return it. If supplied, SLOT is a pre-initialized DSD
+;;; that we modify to get the new slot. This is supplied when handling
+;;; included slots.
 (defun parse-1-dsd (defstruct spec &optional
-                    (islot (make-defstruct-slot-description :%name ""
-                                                            :index 0
-                                                            :type t)))
+                   (slot (make-defstruct-slot-description :%name ""
+                                                          :index 0
+                                                          :type t)))
   (multiple-value-bind (name default default-p type type-p read-only ro-p)
       (cond
        ((listp spec)
                  read-only ro-p)))
        (t
        (when (keywordp spec)
-         ;; FIXME: should be style warning
-         (warn "Keyword slot name indicates probable syntax ~
-                error in DEFSTRUCT -- ~S."
-               spec))
+         (style-warn "Keyword slot name indicates probable syntax ~
+                      error in DEFSTRUCT: ~S."
+                     spec))
        spec))
 
     (when (find name (dd-slots defstruct) :test #'string= :key #'dsd-%name)
-      (error 'program-error
+      (error 'simple-program-error
             :format-control "duplicate slot name ~S"
             :format-arguments (list name)))
-    (setf (dsd-%name islot) (string name))
-    (setf (dd-slots defstruct) (nconc (dd-slots defstruct) (list islot)))
-
-    (let* ((accname (concat-pnames (dd-conc-name defstruct) name))
-          (existing (info :function :accessor-for accname)))
-      (if (and (structure-class-p existing)
-              (not (eq (sb!xc:class-name existing) (dd-name defstruct)))
-              (string= (dsd-%name (find accname
-                                        (dd-slots
-                                         (layout-info
-                                          (class-layout existing)))
-                                        :key #'dsd-accessor))
-                       name))
-       (setf (dsd-accessor islot) nil)
-       (setf (dsd-accessor islot) accname)))
+    (setf (dsd-%name slot) (string name))
+    (setf (dd-slots defstruct) (nconc (dd-slots defstruct) (list slot)))
+
+    (let ((accessor-name (symbolicate (or (dd-conc-name defstruct) "") name))
+         (predicate-name (dd-predicate-name defstruct)))
+      (setf (dsd-accessor-name slot) accessor-name)
+      (when (eql accessor-name predicate-name)
+       ;; Some adventurous soul has named a slot so that its accessor
+       ;; collides with the structure type predicate. ANSI doesn't
+       ;; specify what to do in this case. As of 2001-09-04, Martin
+       ;; Atzmueller reports that CLISP and Lispworks both give
+       ;; priority to the slot accessor, so that the predicate is
+       ;; overwritten. We might as well do the same (as well as
+       ;; signalling a warning).
+       (style-warn
+        "~@<The structure accessor name ~S is the same as the name of the ~
+          structure type predicate. ANSI doesn't specify what to do in ~
+          this case; this implementation chooses to overwrite the type ~
+          predicate with the slot accessor.~@:>"
+        accessor-name)
+       (setf (dd-predicate-name defstruct) nil)))
 
     (when default-p
-      (setf (dsd-default islot) default))
+      (setf (dsd-default slot) default))
     (when type-p
-      (setf (dsd-type islot)
-           (if (eq (dsd-type islot) 't)
+      (setf (dsd-type slot)
+           (if (eq (dsd-type slot) t)
                type
-               `(and ,(dsd-type islot) ,type))))
+               `(and ,(dsd-type slot) ,type))))
     (when ro-p
       (if read-only
-         (setf (dsd-read-only islot) t)
-         (when (dsd-read-only islot)
+         (setf (dsd-read-only slot) t)
+         (when (dsd-read-only slot)
            (error "Slot ~S is :READ-ONLY in parent and must be :READ-ONLY in subtype ~S."
                   name
-                  (dsd-name islot)))))
-    islot))
+                  (dsd-name slot)))))
+    slot))
 
 ;;; When a value of type TYPE is stored in a structure, should it be
 ;;; stored in a raw slot? Return (VALUES RAW? RAW-TYPE WORDS), where
        (setf (dd-raw-index defstruct) (dd-raw-index included-structure))
        (setf (dd-raw-length defstruct) (dd-raw-length included-structure)))
 
-      (dolist (islot (dd-slots included-structure))
-       (let* ((iname (dsd-name islot))
-              (modified (or (find iname modified-slots
+      (dolist (included-slot (dd-slots included-structure))
+       (let* ((included-name (dsd-name included-slot))
+              (modified (or (find included-name modified-slots
                                   :key #'(lambda (x) (if (atom x) x (car x)))
                                   :test #'string=)
-                            `(,iname))))
-         (parse-1-dsd defstruct modified (copy-structure islot)))))))
+                            `(,included-name))))
+         (parse-1-dsd defstruct
+                      modified
+                      (copy-structure included-slot)))))))
 \f
 ;;; This function is called at macroexpand time to compute the INHERITS
 ;;; vector for a structure type definition.
           (let ((old-info (layout-info old-layout)))
             (when (defstruct-description-p old-info)
               (dolist (slot (dd-slots old-info))
-                (fmakunbound (dsd-accessor slot))
+                (fmakunbound (dsd-accessor-name slot))
                 (unless (dsd-read-only slot)
-                  (fmakunbound `(setf ,(dsd-accessor slot)))))))
+                  (fmakunbound `(setf ,(dsd-accessor-name slot)))))))
           (%redefine-defstruct class old-layout layout)
           (setq layout (class-layout class))))
 
 
       (dolist (slot (dd-slots info))
        (let ((dsd slot))
-         (when (and (dsd-accessor slot)
+         (when (and (dsd-accessor-name slot)
                     (eq (dsd-raw-type slot) t))
-           (protect-cl (dsd-accessor slot))
-           (setf (symbol-function (dsd-accessor slot))
+           (protect-cl (dsd-accessor-name slot))
+           (setf (symbol-function (dsd-accessor-name slot))
                  (structure-slot-getter layout dsd))
            (unless (dsd-read-only slot)
-             (setf (fdefinition `(setf ,(dsd-accessor slot)))
+             (setf (fdefinition `(setf ,(dsd-accessor-name slot)))
                    (structure-slot-setter layout dsd))))))
 
       ;; FIXME: See comment on corresponding code in %%COMPILER-DEFSTRUCT.
     ;; GENESIS understands DEFUN but doesn't understand a
     ;; (SETF SYMBOL-FUNCTION) call inside %DEFSTRUCT.)
     #|
-    (let ((pred (dd-predicate info)))
-      (when pred
-       (proclaim-as-defstruct-function-name pred)
+    (let ((predicate-name (dd-predicate-name info)))
+      (when predicate-name
+       (proclaim-as-defstruct-function-name predicate-name)
        (setf (info :function :inlinep pred) :inline)
-       (setf (info :function :inline-expansion pred)
+       (setf (info :function :inline-expansion predicate-name)
              `(lambda (x) (typep x ',name)))))
     |#
 
     (dolist (slot (dd-slots info))
-      (let* ((fun (dsd-accessor slot))
+      (let* ((fun (dsd-accessor-name slot))
             (setf-fun `(setf ,fun)))
        (when (and fun (eq (dsd-raw-type slot) t))
          (proclaim-as-defstruct-function-name fun)
       (let ((type (dd-name info)))
        (setf (info :type :compiler-layout type) nil)
        (undefine-function-name (dd-copier info))
-       (undefine-function-name (dd-predicate info))
+       (undefine-function-name (dd-predicate-name info))
        (dolist (slot (dd-slots info))
-         (let ((fun (dsd-accessor slot)))
+         (let ((fun (dsd-accessor-name slot)))
            (undefine-function-name fun)
            (unless (dsd-read-only slot)
              (undefine-function-name `(setf ,fun))))))
        (t
        (dsd-index slot)))
      (cond
-      ((eq rtype 't) object)
+      ((eq rtype t) object)
       (data)
       (t
        `(truly-the (simple-array (unsigned-byte 32) (*))
     (dolist (slot (dd-slots defstruct))
       (let ((dum (gensym))
            (name (dsd-name slot)))
-       (arglist `((,(intern (string name) "KEYWORD") ,dum)
-                  ,(dsd-default slot)))
+       (arglist `((,(keywordicate name) ,dum) ,(dsd-default slot)))
        (types (dsd-type slot))
        (vals dum)))
     (funcall creator
       (return-from constructor-definitions ()))
 
     (unless (or defaults boas)
-      (push (concat-pnames 'make- (dd-name defstruct)) defaults))
+      (push (symbolicate "MAKE-" (dd-name defstruct)) defaults))
 
     (collect ((res))
       (when defaults
 \f
 ;;;; compiler stuff
 
-;;; Like PROCLAIM-AS-FUNCTION-NAME, but we also set the kind to
+;;; This is like PROCLAIM-AS-FUNCTION-NAME, but we also set the kind to
 ;;; :DECLARED and blow away any ASSUMED-TYPE. Also, if the thing is a
 ;;; slot accessor currently, quietly unaccessorize it. And if there
 ;;; are any undefined warnings, we nuke them.
                     (rest args)))
         (inherits (inherits-for-structure defstruct)))
     (function-%compiler-only-defstruct defstruct inherits)))
+
+(/show0 "code/defstruct.lisp end of file")