0.pre7.117:
[sbcl.git] / src / compiler / ir1opt.lisp
index c7b26e3..b25a775 100644 (file)
                 ;; If next-cont does have a dest, it must be
                 ;; unreachable, since there are no uses.
                 ;; DELETE-CONTINUATION will mark the dest block as
-                ;; delete-p [and also this block, unless it is no
+                ;; DELETE-P [and also this block, unless it is no
                 ;; longer backward reachable from the dest block.]
                 (delete-continuation next-cont)
                 (setf (node-prev next-node) last-cont)
 (defun ir1-optimize-return (node)
   (declare (type creturn node))
   (let* ((tails (lambda-tail-set (return-lambda node)))
-        (funs (tail-set-functions tails)))
+        (funs (tail-set-funs tails)))
     (collect ((res *empty-type* values-type-union))
       (dolist (fun funs)
        (let ((return (lambda-return fun)))
 
       (when (type/= (res) (tail-set-type tails))
        (setf (tail-set-type tails) (res))
-       (dolist (fun (tail-set-functions tails))
+       (dolist (fun (tail-set-funs tails))
          (dolist (ref (leaf-refs fun))
            (reoptimize-continuation (node-cont ref)))))))
 
        (flush-dest test)
        (when (rest (block-succ block))
          (unlink-blocks block victim))
-       (setf (component-reanalyze (block-component (node-block node))) t)
+       (setf (component-reanalyze (node-component node)) t)
        (unlink-node node))))
   (values))
 
-;;; Create a new copy of an IF Node that tests the value of the node
-;;; Use. The test must have >1 use, and must be immediately used by
-;;; Use. Node must be the only node in its block (implying that
+;;; Create a new copy of an IF node that tests the value of the node
+;;; USE. The test must have >1 use, and must be immediately used by
+;;; USE. NODE must be the only node in its block (implying that
 ;;; block-start = if-test).
 ;;;
 ;;; This optimization has an effect semantically similar to the
 ;;; become unreachable, resulting in a spurious note.
 (defun convert-if-if (use node)
   (declare (type node use) (type cif node))
-  (with-ir1-environment node
+  (with-ir1-environment-from-node node
     (let* ((block (node-block node))
           (test (if-test node))
           (cblock (if-consequent node))
                              :consequent cblock
                              :alternative ablock))
           (new-block (continuation-starts-block new-cont)))
-      (prev-link new-node new-cont)
+      (link-node-to-previous-continuation new-node new-cont)
       (setf (continuation-dest new-cont) new-node)
       (add-continuation-use new-node dummy-cont)
       (setf (block-last new-block) new-node)
                 (change-ref-leaf ref res))))
        (if ir1-p
            (frob)
-           (with-ir1-environment call
+           (with-ir1-environment-from-node call
              (frob)
-             (local-call-analyze *current-component*))))
+             (locall-analyze-component *current-component*))))
 
       (values (ref-leaf (continuation-use (basic-combination-fun call)))
              nil))
 ;;; integrated into the control flow.
 (defun transform-call (node res)
   (declare (type combination node) (list res))
-  (with-ir1-environment node
+  (with-ir1-environment-from-node node
     (let ((new-fun (ir1-convert-inline-lambda
                    res
-                   :debug-name "<something inlined in TRANSFORM-CALL>"))
+                   :debug-name "something inlined in TRANSFORM-CALL"))
          (ref (continuation-use (combination-fun node))))
       (change-ref-leaf ref new-fun)
       (setf (combination-kind node) :full)
-      (local-call-analyze *current-component*)))
+      (locall-analyze-component *current-component*)))
   (values))
 
 ;;; Replace a call to a foldable function of constant arguments with
 ;;; changes. We look at each changed argument. If the corresponding
 ;;; variable is set, then we call PROPAGATE-FROM-SETS. Otherwise, we
 ;;; consider substituting for the variable, and also propagate
-;;; derived-type information for the arg to all the Var's refs.
+;;; derived-type information for the arg to all the VAR's refs.
 ;;;
 ;;; Substitution is inhibited when the arg leaf's derived type isn't a
 ;;; subtype of the argument's asserted type. This prevents type
 ;;; are done, then we delete the LET.
 ;;;
 ;;; Note that we are responsible for clearing the
-;;; Continuation-Reoptimize flags.
+;;; CONTINUATION-REOPTIMIZE flags.
 (defun propagate-let-args (call fun)
   (declare (type combination call) (type clambda fun))
   (loop for arg in (combination-args call)
                         (values-subtypep (leaf-type leaf)
                                          (continuation-asserted-type arg)))
                (propagate-to-refs var (continuation-type arg))
-               (let ((this-comp (block-component (node-block use))))
+               (let ((use-component (node-component use)))
                  (substitute-leaf-if
                   #'(lambda (ref)
-                      (cond ((eq (block-component (node-block ref))
-                                 this-comp)
+                      (cond ((eq (node-component ref) use-component)
                              t)
                             (t
-                             (aver (eq (functional-kind (lambda-home fun))
-                                       :toplevel))
+                             (aver (lambda-toplevelish-p (lambda-home fun)))
                              nil)))
                   leaf var))
                t)))))
 (defun propagate-local-call-args (call fun)
   (declare (type combination call) (type clambda fun))
 
-  (unless (or (functional-entry-function fun)
+  (unless (or (functional-entry-fun fun)
              (lambda-optional-dispatch fun))
     (let* ((vars (lambda-vars fun))
           (union (mapcar #'(lambda (arg var)
                            min)
                           (t nil))))
          (when count
-           (with-ir1-environment node
+           (with-ir1-environment-from-node node
              (let* ((dums (make-gensym-list count))
                     (ignore (gensym))
                     (fun (ir1-convert-lambda
                              (funcall ,(ref-leaf ref) ,@dums)))))
                (change-ref-leaf ref fun)
                (aver (eq (basic-combination-kind node) :full))
-               (local-call-analyze *current-component*)
+               (locall-analyze-component *current-component*)
                (aver (eq (basic-combination-kind node) :local)))))))))
   (values))
 
               (mapc #'flush-dest (subseq vals nvars))
               (setq vals (subseq vals 0 nvars)))
              ((< nvals nvars)
-              (with-ir1-environment use
+              (with-ir1-environment-from-node use
                 (let ((node-prev (node-prev use)))
                   (setf (node-prev use) nil)
                   (setf (continuation-next node-prev) nil)
                           do (reference-constant prev cont nil)
                              (res cont))
                     (setq vals (res)))
-                  (prev-link use (car (last vals)))))))
+                  (link-node-to-previous-continuation use
+                                                      (car (last vals)))))))
        (setf (combination-args use) vals)
        (flush-dest (combination-fun use))
        (let ((fun-cont (basic-combination-fun call)))