sbcl-0.8.14.11:
[sbcl.git] / src / compiler / ir1-translators.lisp
index cae654d..d954575 100644 (file)
@@ -58,7 +58,7 @@
 ;;;; node.
 
 ;;; Make a :ENTRY cleanup and emit an ENTRY node, then convert the
-;;; body in the modified environment. We make CONT start a block now,
+;;; body in the modified environment. We make NEXT start a block now,
 ;;; since if it was done later, the block would be in the wrong
 ;;; environment.
 (def-ir1-translator block ((name &rest forms) start next result)
@@ -69,6 +69,7 @@
   result of Value-Form."
   (unless (symbolp name)
     (compiler-error "The block name ~S is not a symbol." name))
+  (start-block start)
   (ctran-starts-block next)
   (let* ((dummy (make-ctran))
         (entry (make-entry))
   Evaluate the Value-Form, returning its values from the lexically enclosing
   BLOCK Block-Name. This is constrained to be used only within the dynamic
   extent of the BLOCK."
-  ;; CMU CL comment:
-  ;;   We make CONT start a block just so that it will have a block
-  ;;   assigned. People assume that when they pass a continuation into
-  ;;   IR1-CONVERT as CONT, it will have a block when it is done.
+  ;; old comment:
+  ;;   We make NEXT start a block just so that it will have a block
+  ;;   assigned. People assume that when they pass a ctran into
+  ;;   IR1-CONVERT as NEXT, it will have a block when it is done.
   ;; KLUDGE: Note that this block is basically fictitious. In the code
   ;;   (BLOCK B (RETURN-FROM B) (SETQ X 3))
   ;; it's the block which answers the question "which block is
   to the next statement following that tag. A Tag must an integer or a
   symbol. A statement must be a list. Other objects are illegal within the
   body."
+  (start-block start)
   (ctran-starts-block next)
   (let* ((dummy (make-ctran))
         (entry (make-entry))
     (compiler-style-warn "duplicate definitions in ~S" definitions))
   (let* ((processed-definitions (mapcar definitionize-fun definitions))
          (*lexenv* (make-lexenv definitionize-keyword processed-definitions)))
+    ;; I wonder how much of an compiler performance penalty this
+    ;; non-constant keyword is.
     (funcall fun definitionize-keyword processed-definitions)))
 
 ;;; Tweak LEXENV to include the DEFINITIONS from a MACROLET, then
       (destructuring-bind (name arglist &body body) definition
         (unless (symbolp name)
           (fail "The local macro name ~S is not a symbol." name))
+       (when (fboundp name)
+         (compiler-assert-symbol-home-package-unlocked
+           name "binding ~A as a local macro"))
         (unless (listp arglist)
           (fail "The local macro argument list ~S is not a list."
                 arglist))
       (destructuring-bind (name expansion) definition
         (unless (symbolp name)
           (fail "The local symbol macro name ~S is not a symbol." name))
+       (when (or (boundp name) (eq (info :variable :kind name) :macro))
+         (compiler-assert-symbol-home-package-unlocked
+           name "binding ~A as a local symbol-macro"))
         (let ((kind (info :variable :kind name)))
           (when (member kind '(:special :constant))
             (fail "Attempt to bind a ~(~A~) variable with SYMBOL-MACROLET: ~S"
                   kind name)))
+       ;; A magical cons that MACROEXPAND-1 understands.
         `(,name . (MACRO . ,expansion))))))
 
 (defun funcall-in-symbol-macrolet-lexenv (definitions fun context)
                 '(lambda named-lambda instance-lambda lambda-with-lexenv))
         (ir1-convert-lambdalike
                          thing
-                         :debug-name (debug-namify "#'~S" thing)
+                         :debug-name (debug-namify "#'" thing)
                          :allow-debug-catch-tag t))
        ((legal-fun-name-p thing)
         (find-lexically-apparent-fun
   (if (and (consp function) (eq (car function) 'function))
       (ir1-convert start next result
                    `(,(fun-name-leaf (second function)) ,@args))
-      (let ((fun-ctran (make-ctran))
+      (let ((ctran (make-ctran))
             (fun-lvar (make-lvar)))
-        (ir1-convert start fun-ctran fun-lvar `(the function ,function))
-        (ir1-convert-combination-args fun-ctran fun-lvar next result args))))
+        (ir1-convert start ctran fun-lvar `(the function ,function))
+        (ir1-convert-combination-args fun-lvar ctran next result args))))
 
 ;;; This source transform exists to reduce the amount of work for the
 ;;; compiler. If the called function is a FUNCTION form, then convert
       `(%funcall ,function ,@args)
       (values nil t)))
 
-(deftransform %coerce-callable-to-fun ((thing) (function) *
-                                      :important t)
+(deftransform %coerce-callable-to-fun ((thing) (function) *)
   "optimize away possible call to FDEFINITION at runtime"
   'thing)
 \f
                 (vars var)
                 (names name)
                 (vals (second spec)))))))
-
+    (dolist (name (names))
+      (when (eq (info :variable :kind name) :macro)
+       (compiler-assert-symbol-home-package-unlocked
+         name "lexically binding symbol-macro ~A")))
     (values (vars) (vals))))
 
 (def-ir1-translator let ((bindings &body body) start next result)
       (multiple-value-bind (forms decls)
           (parse-body body :doc-string-allowed nil)
         (multiple-value-bind (vars values) (extract-let-vars bindings 'let)
-          (binding* ((fun-ctran (make-ctran))
+          (binding* ((ctran (make-ctran))
                      (fun-lvar (make-lvar))
                      ((next result)
                       (processing-decls (decls vars nil next result)
                         (let ((fun (ir1-convert-lambda-body
-                                    forms vars
-                                    :debug-name (debug-namify "LET ~S"
+                                    forms
+                                    vars
+                                    :debug-name (debug-namify "LET S"
                                                               bindings))))
-                          (reference-leaf start fun-ctran fun-lvar fun))
+                          (reference-leaf start ctran fun-lvar fun))
                         (values next result))))
-            (ir1-convert-combination-args fun-ctran fun-lvar next result values))))))
+            (ir1-convert-combination-args fun-lvar ctran next result values))))))
 
 (def-ir1-translator let* ((bindings &body body)
                          start next result)
       (parse-body body :doc-string-allowed nil)
     (multiple-value-bind (vars values) (extract-let-vars bindings 'let*)
       (processing-decls (decls vars nil start next)
-        (ir1-convert-aux-bindings start next result forms vars values)))))
+        (ir1-convert-aux-bindings start 
+                                  next 
+                                  result
+                                  forms
+                                  vars 
+                                  values)))))
 
 ;;; logic shared between IR1 translators for LOCALLY, MACROLET,
 ;;; and SYMBOL-MACROLET
 
       (let ((name (first def)))
        (check-fun-name name)
+       (when (fboundp name)
+         (compiler-assert-symbol-home-package-unlocked
+           name "binding ~A as a local function"))
        (names name)
        (multiple-value-bind (forms decls) (parse-body (cddr def))
          (defs `(lambda ,(second def)
   (multiple-value-bind (forms decls)
       (parse-body body :doc-string-allowed nil)
     (multiple-value-bind (names defs)
-       (extract-flet-vars definitions 'flet)
+        (extract-flet-vars definitions 'flet)
       (let ((fvars (mapcar (lambda (n d)
                              (ir1-convert-lambda d
                                                  :source-name n
                                                  :debug-name (debug-namify
-                                                              "FLET ~S" n)
+                                                              "FLET " n)
                                                  :allow-debug-catch-tag t))
                            names defs)))
         (processing-decls (decls nil fvars next result)
           (let ((*lexenv* (make-lexenv :funs (pairlis names fvars))))
-            (ir1-convert-progn-body start next result forms)))))))
+            (ir1-convert-progn-body start 
+                                    next 
+                                    result
+                                    forms)))))))
 
 (def-ir1-translator labels ((definitions &body body) start next result)
   #!+sb-doc
   each other."
   (multiple-value-bind (forms decls) (parse-body body :doc-string-allowed nil)
     (multiple-value-bind (names defs)
-       (extract-flet-vars definitions 'labels)
-      (let* ( ;; dummy LABELS functions, to be used as placeholders
+        (extract-flet-vars definitions 'labels)
+      (let* (;; dummy LABELS functions, to be used as placeholders
              ;; during construction of real LABELS functions
-            (placeholder-funs (mapcar (lambda (name)
-                                        (make-functional
-                                         :%source-name name
-                                         :%debug-name (debug-namify
-                                                       "LABELS placeholder ~S"
-                                                       name)))
-                                      names))
-            ;; (like PAIRLIS but guaranteed to preserve ordering:)
-            (placeholder-fenv (mapcar #'cons names placeholder-funs))
+             (placeholder-funs (mapcar (lambda (name)
+                                         (make-functional
+                                          :%source-name name
+                                          :%debug-name (debug-namify
+                                                        "LABELS placeholder "
+                                                        name)))
+                                       names))
+             ;; (like PAIRLIS but guaranteed to preserve ordering:)
+             (placeholder-fenv (mapcar #'cons names placeholder-funs))
              ;; the real LABELS functions, compiled in a LEXENV which
              ;; includes the dummy LABELS functions
-            (real-funs
-             (let ((*lexenv* (make-lexenv :funs placeholder-fenv)))
-               (mapcar (lambda (name def)
-                         (ir1-convert-lambda def
-                                             :source-name name
-                                             :debug-name (debug-namify
-                                                          "LABELS ~S" name)
-                                             :allow-debug-catch-tag t))
-                       names defs))))
-
+             (real-funs
+              (let ((*lexenv* (make-lexenv :funs placeholder-fenv)))
+                (mapcar (lambda (name def)
+                          (ir1-convert-lambda def
+                                              :source-name name
+                                              :debug-name (debug-namify
+                                                           "LABELS " name)
+                                              :allow-debug-catch-tag t))
+                        names defs))))
+        
         ;; Modify all the references to the dummy function leaves so
         ;; that they point to the real function leaves.
-       (loop for real-fun in real-funs and
-             placeholder-cons in placeholder-fenv do
-             (substitute-leaf real-fun (cdr placeholder-cons))
-             (setf (cdr placeholder-cons) real-fun))
-
+        (loop for real-fun in real-funs and
+              placeholder-cons in placeholder-fenv do
+              (substitute-leaf real-fun (cdr placeholder-cons))
+              (setf (cdr placeholder-cons) real-fun))
+        
         ;; Voila.
-       (processing-decls (decls nil real-funs next result)
+        (processing-decls (decls nil real-funs next result)
           (let ((*lexenv* (make-lexenv
                            ;; Use a proper FENV here (not the
                            ;; placeholder used earlier) so that if the
                            ;; lexical environment is used for inline
                            ;; expansion we'll get the right functions.
                            :funs (pairlis names real-funs))))
-            (ir1-convert-progn-body start next result forms)))))))
+            (ir1-convert-progn-body start 
+                                    next 
+                                    result
+                                    forms)))))))
+
 \f
 ;;;; the THE special operator, and friends
 
 (def-ir1-translator truly-the ((type value) start next result)
   #!+sb-doc
   ""
-  (declare (inline member))
   #-nil
   (let ((type (coerce-to-values (compiler-values-specifier-type type)))
-       (old (find-uses result)))
+       (old (when result (find-uses result))))
     (ir1-convert start next result value)
-    (do-uses (use result)
-      (unless (memq use old)
-       (derive-node-type use type))))
+    (when result
+      (do-uses (use result)
+        (unless (memq use old)
+          (derive-node-type use type)))))
   #+nil
   (the-in-policy type value '((type-check . 0)) start cont))
 \f
   (let ((fun (ir1-convert-lambda
              `(lambda ()
                 (return-from ,tag (%unknown-values)))
-             :debug-name (debug-namify "escape function for ~S" tag))))
+             :debug-name (debug-namify "escape function for " tag))))
     (setf (functional-kind fun) :escape)
     (reference-leaf start next result fun)))
 
    (with-unique-names (exit-block)
      `(block ,exit-block
        (%within-cleanup
-           :catch
-           (%catch (%escape-fun ,exit-block) ,tag)
-         ,@body)))))
+        :catch (%catch (%escape-fun ,exit-block) ,tag)
+        ,@body)))))
 
 (def-ir1-translator unwind-protect
     ((protected &body cleanup) start next result)
   "MULTIPLE-VALUE-CALL Function Values-Form*
   Call FUNCTION, passing all the values of each VALUES-FORM as arguments,
   values from the first VALUES-FORM making up the first argument, etc."
-  (let* ((fun-ctran (make-ctran))
+  (let* ((ctran (make-ctran))
          (fun-lvar (make-lvar))
         (node (if args
                   ;; If there are arguments, MULTIPLE-VALUE-CALL
                   ;; important for simplifying compilation of
                   ;; MV-COMBINATIONS.
                   (make-combination fun-lvar))))
-    (ir1-convert start fun-ctran fun-lvar
+    (ir1-convert start ctran fun-lvar
                 (if (and (consp fun) (eq (car fun) 'function))
                     fun
                     `(%coerce-callable-to-fun ,fun)))
     (setf (lvar-dest fun-lvar) node)
     (collect ((arg-lvars))
-      (let ((this-start fun-ctran))
+      (let ((this-start ctran))
        (dolist (arg args)
          (let ((this-ctran (make-ctran))
                 (this-lvar (make-lvar node)))
        (use-continuation node next result)
        (setf (basic-combination-args node) (arg-lvars))))))
 
-;;; MULTIPLE-VALUE-PROG1 is represented implicitly in IR1 by having a
-;;; the result code use result continuation (CONT), but transfer
-;;; control to the evaluation of the body. In other words, the result
-;;; continuation isn't IMMEDIATELY-USED-P by the nodes that compute
-;;; the result.
-;;;
-;;; In order to get the control flow right, we convert the result with
-;;; a dummy result continuation, then convert all the uses of the
-;;; dummy to be uses of CONT. If a use is an EXIT, then we also
-;;; substitute CONT for the dummy in the corresponding ENTRY node so
-;;; that they are consistent. Note that this doesn't amount to
-;;; changing the exit target, since the control destination of an exit
-;;; is determined by the block successor; we are just indicating the
-;;; continuation that the result is delivered to.
-;;;
-;;; We then convert the body, using another dummy continuation in its
-;;; own block as the result. After we are done converting the body, we
-;;; move all predecessors of the dummy end block to CONT's block.
-;;;
-;;; Note that we both exploit and maintain the invariant that the CONT
-;;; to an IR1 convert method either has no block or starts the block
-;;; that control should transfer to after completion for the form.
-;;; Nested MV-PROG1's work because during conversion of the result
-;;; form, we use dummy continuation whose block is the true control
-;;; destination.
 (def-ir1-translator multiple-value-prog1
     ((values-form &rest forms) start next result)
   #!+sb-doc
   Evaluate Values-Form and then the Forms, but return all the values of
   Values-Form."
   (let ((dummy (make-ctran)))
+    (ctran-starts-block dummy)
     (ir1-convert start dummy result values-form)
     (ir1-convert-progn-body dummy next nil forms)))
 \f