0.7.12.47:
[sbcl.git] / src / code / defboot.lisp
index d9afbde..e2bd2c2 100644 (file)
     (error "Vars is not a list of symbols: ~S" vars)))
 
 (defmacro-mundanely multiple-value-setq (vars value-form)
-  (cond ((null vars)
-        ;; The ANSI spec says that the primary value of VALUE-FORM must be
-        ;; returned. The general-case-handling code below doesn't do this
-        ;; correctly in the special case when there are no vars bound, so we
-        ;; handle this special case separately here.
-        (let ((g (gensym)))
-          `(multiple-value-bind (,g) ,value-form
-             ,g)))
-       ((list-of-symbols-p vars)
-        (let ((temps (make-gensym-list (length vars))))
-          `(multiple-value-bind ,temps ,value-form
-             ,@(mapcar (lambda (var temp)
-                         `(setq ,var ,temp))
-                       vars temps)
-             ,(car temps))))
-       (t (error "Vars is not a list of symbols: ~S" vars))))
+  (unless (list-of-symbols-p vars)
+    (error "Vars is not a list of symbols: ~S" vars))
+  `(values (setf (values ,@vars) ,value-form)))
 
 (defmacro-mundanely multiple-value-list (value-form)
   `(multiple-value-call #'list ,value-form))
    ;; the only unsurprising choice.
    (info :function :inline-expansion-designator name)))
 
-;;; Now that we have the definition of MULTIPLE-VALUE-BIND, we can
-;;; make a reasonably readable definition of DEFUN.
 (defmacro-mundanely defun (&environment env name args &body body)
   "Define a function at top level."
   #+sb-xc-host
            #-sb-xc-host
           (named-lambda `(named-lambda ,name ,@lambda-guts))
           (inline-lambda
-           (cond (;; Does the user not even want to inline?
-                  (not (inline-fun-name-p name))
-                  nil)
-                 (;; Does inlining look too hairy to handle?
-                  (not (sb!c:lambda-independent-of-lexenv-p lambda env))
-                  (sb!c:maybe-compiler-note
-                   "lexical environment too hairy, can't inline DEFUN ~S"
-                   name)
-                  nil)
-                 (t
-                  ;; FIXME: The only reason that we return
-                  ;; LAMBDA-WITH-LEXENV instead of returning bare
-                  ;; LAMBDA is to avoid modifying downstream code
-                  ;; which expects LAMBDA-WITH-LEXENV. But the code
-                  ;; here is the only code which feeds into the
-                  ;; downstream code, and the generality of the
-                  ;; interface is no longer used, so it'd make sense
-                  ;; to simplify the interface instead of using the
-                  ;; old general LAMBDA-WITH-LEXENV interface in this
-                  ;; simplified way.
-                  `(sb!c:lambda-with-lexenv
-                    nil nil nil ; i.e. no DECLS, no MACROS, no SYMMACS
-                    ,@lambda-guts)))))
+           (when (inline-fun-name-p name)
+             ;; we want to attempt to inline, so complain if we can't
+             (or (sb!c:maybe-inline-syntactic-closure lambda env)
+                 (progn
+                   (#+sb-xc-host warn
+                    #-sb-xc-host sb!c:maybe-compiler-note
+                    "lexical environment too hairy, can't inline DEFUN ~S"
+                    name)
+                   nil)))))
       `(progn
 
         ;; In cross-compilation of toplevel DEFUNs, we arrange
   #+nil (setf (%fun-name def) name)
 
   (when doc
-    ;; FIXME: This should use shared SETF-name-parsing logic.
-    (if (and (consp name) (eq (first name) 'setf))
-       (setf (fdocumentation (second name) 'setf) doc)
-       (setf (fdocumentation (the symbol name) 'function) doc)))
+    (setf (fdocumentation name 'function) doc))
   name)
 \f
 ;;;; DEFVAR and DEFPARAMETER
         `((unless (boundp ',var)
             (setq ,var ,val))))
      ,@(when docp
-        `((funcall #'(setf fdocumentation) ',doc ',var 'variable)))
+        `((setf (fdocumentation ',var 'variable) ',doc )))
      ',var))
 
 (defmacro-mundanely defparameter (var val &optional (doc nil docp))
      (declaim (special ,var))
      (setq ,var ,val)
      ,@(when docp
-        ;; FIXME: The various FUNCALL #'(SETF FDOCUMENTATION) and
-        ;; other FUNCALL #'(SETF FOO) forms in the code should
-        ;; unbogobootstrapized back to ordinary SETF forms.
-        `((funcall #'(setf fdocumentation) ',doc ',var 'variable)))
+        `((setf (fdocumentation ',var 'variable) ',doc)))
      ',var))
 \f
 ;;;; iteration constructs
 ;;; defined that it looks as though it's worth just implementing them
 ;;; ASAP, at the cost of being unable to use the standard
 ;;; destructuring mechanisms.
-(defmacro-mundanely dotimes (var-count-result &body body)
-  (multiple-value-bind ; to roll our own destructuring
-      (var count result)
-      (apply (lambda (var count &optional (result nil))
-              (values var count result))
-            var-count-result)
-    (cond ((numberp count)
-          `(do ((,var 0 (1+ ,var)))
-               ((>= ,var ,count) ,result)
-             (declare (type unsigned-byte ,var))
-             ,@body))
-         (t (let ((v1 (gensym)))
-              `(do ((,var 0 (1+ ,var)) (,v1 ,count))
-                   ((>= ,var ,v1) ,result)
-                 (declare (type unsigned-byte ,var))
-                 ,@body))))))
-(defmacro-mundanely dolist (var-list-result &body body)
-  (multiple-value-bind ; to roll our own destructuring
-      (var list result)
-      (apply (lambda (var list &optional (result nil))
-              (values var list result))
-            var-list-result)
-    ;; We repeatedly bind the var instead of setting it so that we
-    ;; never have to give the var an arbitrary value such as NIL
-    ;; (which might conflict with a declaration). If there is a result
-    ;; form, we introduce a gratuitous binding of the variable to NIL
-    ;; without the declarations, then evaluate the result form in that
-    ;; environment. We spuriously reference the gratuitous variable,
-    ;; since since we don't want to use IGNORABLE on what might be a
-    ;; special var.
+(defmacro-mundanely dotimes ((var count &optional (result nil)) &body body)
+  (cond ((numberp count)
+        `(do ((,var 0 (1+ ,var)))
+          ((>= ,var ,count) ,result)
+          (declare (type unsigned-byte ,var))
+          ,@body))
+       (t (let ((v1 (gensym)))
+            `(do ((,var 0 (1+ ,var)) (,v1 ,count))
+              ((>= ,var ,v1) ,result)
+              (declare (type unsigned-byte ,var))
+              ,@body)))))
+
+(defmacro-mundanely dolist ((var list &optional (result nil)) &body body)
+  ;; We repeatedly bind the var instead of setting it so that we never
+  ;; have to give the var an arbitrary value such as NIL (which might
+  ;; conflict with a declaration). If there is a result form, we
+  ;; introduce a gratuitous binding of the variable to NIL without the
+  ;; declarations, then evaluate the result form in that
+  ;; environment. We spuriously reference the gratuitous variable,
+  ;; since we don't want to use IGNORABLE on what might be a special
+  ;; var.
+  (multiple-value-bind (forms decls) (parse-body body nil)
     (let ((n-list (gensym)))
-      `(do ((,n-list ,list (cdr ,n-list)))
-          ((endp ,n-list)
-           ,@(if result
-               `((let ((,var nil))
-                   ,var
-                   ,result))
-               '(nil)))
-        (let ((,var (car ,n-list)))
-          ,@body)))))
+      `(do* ((,n-list ,list (cdr ,n-list)))
+       ((endp ,n-list)
+        ,@(if result
+              `((let ((,var nil))
+                  ,var
+                  ,result))
+              '(nil)))
+       (let ((,var (car ,n-list)))
+         ,@decls
+         (tagbody
+            ,@forms))))))
 \f
 ;;;; miscellaneous
 
 
 (defmacro-mundanely psetq (&rest pairs)
   #!+sb-doc
-  "SETQ {var value}*
+  "PSETQ {var value}*
    Set the variables to the values, like SETQ, except that assignments
    happen in parallel, i.e. no assignments take place until all the
    forms have been evaluated."
-  ;; (This macro is used in the definition of DO, so we can't use DO in the
-  ;; definition of this macro without getting into confusing bootstrap issues.)
-  (prog ((lets nil)
-        (setqs nil)
-        (pairs pairs))
-    :again
-    (when (atom (cdr pairs))
-      (return `(let ,(nreverse lets)
-                (setq ,@(nreverse setqs))
-                nil)))
-    (let ((gen (gensym)))
-      (setq lets (cons `(,gen ,(cadr pairs)) lets)
-           setqs (list* gen (car pairs) setqs)
-           pairs (cddr pairs)))
-    (go :again)))
+  ;; Given the possibility of symbol-macros, we delegate to PSETF
+  ;; which knows how to deal with them, after checking that syntax is
+  ;; compatible with PSETQ.
+  (do ((pair pairs (cddr pair)))
+      ((endp pair) `(psetf ,@pairs))
+    (unless (symbolp (car pair))
+      (error 'simple-program-error
+            :format-control "variable ~S in PSETQ is not a SYMBOL"
+            :format-arguments (list (car pair))))))
 
 (defmacro-mundanely lambda (&whole whole args &body body)
   (declare (ignore args body))
   `#',whole)
+
+(defmacro-mundanely named-lambda (&whole whole name args &body body)
+  (declare (ignore name args body))
+  `#',whole)
+
+(defmacro-mundanely lambda-with-lexenv (&whole whole
+                                       declarations macros symbol-macros
+                                       &body body)
+  (declare (ignore declarations macros symbol-macros body))
+  `#',whole)