Skip to content
Snippets Groups Projects
ir1util.lisp 53.1 KiB
Newer Older
wlott's avatar
wlott committed
;;; -*- Package: C; Log: C.Log -*-
;;;
;;; **********************************************************************
;;; This code was written as part of the Spice Lisp project at
;;; Carnegie-Mellon University, and has been placed in the public domain.
;;; If you want to use this code or any part of Spice Lisp, please contact
;;; Scott Fahlman (FAHLMAN@CMUC). 
;;; **********************************************************************
;;;
;;;    This file contains random utilities used for manipulating the IR1
;;; representation.
;;;
;;; Written by Rob MacLachlan
;;;
(in-package 'c)


;;;; Cleanup hackery:

;;; Find-Enclosing-Cleanup  --  Interface
;;;
;;;    Chain up the Lambda-Cleanup thread until we find a Cleanup or null.
;;;
(defun find-enclosing-cleanup (thing)
  (declare (type (or cleanup clambda null) thing))
  (etypecase thing
    ((or cleanup null) thing)
    (clambda (find-enclosing-cleanup (lambda-cleanup thing)))))


;;; Insert-Cleanup-Code  --  Interface
;;;
;;;    Convert the Form in a block inserted between Block1 and Block2 as an
;;; implicit MV-Prog1.  The inserted block is returned.  Node is used for IR1
;;; context when converting the form.  Note that the block is not assigned a
;;; number, and is linked into the DFO at the beginning.  We indicate that we
;;; have trashed the DFO by setting Component-Reanalyze.
;;;
(defun insert-cleanup-code (block1 block2 node form)
  (declare (type cblock block1 block2) (type node node))
  (with-ir1-environment node
    (setf (component-reanalyze *current-component*) t)
    (let* ((start (make-continuation))
	   (block (continuation-starts-block start))
	   (cont (make-continuation)))
      (change-block-successor block1 block2 block)
      (link-blocks block block2)
      (ir1-convert start cont form)
      (setf (block-last block) (continuation-use cont))
      block)))
  

;;;; Continuation use hacking:

;;; Find-Uses  --  Interface
;;;
;;;    Return a list of all the nodes which use Cont.
;;;
(proclaim '(function find-uses (continuation) list))
(defun find-uses (cont)
  (ecase (continuation-kind cont)
    ((:block-start :deleted-block-start)
     (block-start-uses (continuation-block cont)))
    (:inside-block (list (continuation-use cont)))
    (:unused nil)))

      
;;; Delete-Continuation-Use  --  Interface
;;;
;;;    Update continuation use information so that Node is no longer a use of
;;; its Cont.  If the old continuation doesn't start its block, then we don't
;;; update the Block-Start-Uses, since it will be deleted when we are done.
;;;
;;; Note: if you call this function, you may have to do a
;;; REOPTIMIZE-CONTINUATION to inform IR1 optimization that something has
;;; changed.
;;;
(proclaim '(function delete-continuation-use (node) void))
(defun delete-continuation-use (node)
  (let* ((cont (node-cont node))
	 (block (continuation-block cont)))
    (ecase (continuation-kind cont)
      (:deleted)
      ((:block-start :deleted-block-start)
       (let ((uses (delete node (block-start-uses block))))
	 (setf (block-start-uses block) uses)
	 (setf (continuation-use cont)
	       (if (cdr uses) nil (car uses)))))
      (:inside-block
       (setf (continuation-kind cont) :unused)
       (setf (continuation-block cont) nil)
       (setf (continuation-use cont) nil)
       (setf (continuation-next cont) nil)))
    (setf (node-cont node) nil)))


;;; Add-Continuation-Use  --  Interface
;;;
;;;    Update continuation use information so that Node uses Cont.  If Cont is
;;; :Unused, then we set its block to Node's Node-Block (which must be set.)
;;;
;;; Note: if you call this function, you may have to do a
;;; REOPTIMIZE-CONTINUATION to inform IR1 optimization that something has
;;; changed.
;;;
(proclaim '(function add-continuation-use (node continuation) void))
(defun add-continuation-use (node cont)
  (assert (not (node-cont node)))
  (let ((block (continuation-block cont)))
    (ecase (continuation-kind cont)
      (:deleted)
      (:unused
       (assert (not block))
       (let ((block (node-block node)))
	 (assert block)
	 (setf (continuation-block cont) block))
       (setf (continuation-kind cont) :inside-block)
       (setf (continuation-use cont) node))
      ((:block-start :deleted-block-start)
       (let ((uses (cons node (block-start-uses block))))
	 (setf (block-start-uses block) uses)
	 (setf (continuation-use cont)
	       (if (cdr uses) nil (car uses)))))))
  (setf (node-cont node) cont))


;;; Immediately-Used-P  --  Interface
;;;
;;;    Return true if Cont is the Node-Cont for Node and Cont is transferred to
;;; immediately after the evaluation of Node.
;;;
(defun immediately-used-p (cont node)
  (declare (type continuation cont) (type node node))
  (and (eq (node-cont node) cont)
       (not (eq (continuation-kind cont) :deleted))
       (let ((cblock (continuation-block cont))
	     (nblock (node-block node)))
	 (or (eq cblock nblock)
	     (let ((succ (block-succ nblock)))
	       (and (= (length succ) 1)
		    (eq (first succ) cblock)))))))


;;;; Continuation substitution:

;;; Substitute-Continuation  --  Interface
;;;
;;;    In Old's Dest, replace Old with New.  New's Dest must initially be NIL.
;;; When we are done, we call Flush-Dest on Old to clear its Dest and to note
;;; potential optimization opportunities.
;;;
(defun substitute-continuation (new old)
  (declare (type continuation old new))
  (assert (not (continuation-dest new)))
  (let ((dest (continuation-dest old)))
    (etypecase dest
      ((or ref bind))
      (cif (setf (if-test dest) new))
      (cset (setf (set-value dest) new))
      (creturn (setf (return-result dest) new))
      (exit (setf (exit-value dest) new))
      (basic-combination
       (if (eq old (basic-combination-fun dest))
	   (setf (basic-combination-fun dest) new)
	   (setf (basic-combination-args dest)
		 (nsubst new old (basic-combination-args dest))))))

    (flush-dest old)
    (setf (continuation-dest new) dest))
  (undefined-value))


;;; Ensure-Block-Start  --  Interface
;;;
;;;    Ensure that Cont is the start of a block (or deleted) so that the use
;;; set can be freely manipulated.
;;; -- If the continuation is :Unused or is :Inside-Block and the Cont of Last
;;;    in its block, then we make it the start of a new deleted block.
;;; -- If the continuation is :Inside-Block inside a block, then we split the
;;;    block using Node-Ends-Block, which makes the continuation be a
;;;    :Block-Start.
;;;
(defun ensure-block-start (cont)
  (declare (type continuation cont))
  (let ((kind (continuation-kind cont)))
    (ecase kind
      ((:deleted :block-start :deleted-block-start))
      ((:unused :inside-block)
       (let ((block (continuation-block cont)))
	 (cond ((or (eq kind :unused)
		    (eq (node-cont (block-last block)) cont))
		(setf (continuation-block cont)
		      (make-block-key :start cont :lambda nil
				      :start-cleanup nil :end-cleanup nil
				      :component nil))
		(setf (continuation-kind cont) :deleted-block-start))
	       (t
		(node-ends-block (continuation-use cont))))))))
  (undefined-value))


;;; Substitute-Continuation-Uses  --  Interface
;;;
;;;    Replace all uses of Old with uses of New, where New has an arbitary
;;; number of uses.  If a use is an Exit, then we also substitute New for Old
;;; in the Entry's Exits to maintain consistency between the two.
;;;
;;;    If New will end up with more than one use, then we must arrange for it
;;; to start a block if it doesn't already.
;;;
(defun substitute-continuation-uses (new old)
  (declare (type continuation old new))
  (unless (and (eq (continuation-kind new) :unused)
	       (eq (continuation-kind old) :inside-block))
    (ensure-block-start new))
  
  (do-uses (node old)
    (when (exit-p node)
      (let ((entry (exit-entry node)))
	(when entry
	  (setf (entry-exits entry)
		(nsubst new old (entry-exits entry))))))
    (delete-continuation-use node)
    (add-continuation-use node new))

  (reoptimize-continuation new)
  (undefined-value))

#|
;;; Substitute-Node-Cont  --  Interface
;;;
;;;    Replace Old's single use with a use of New.  This is used in contexts
;;; where we know that New has no use and Old has a single use.
;;;
(defun substitute-node-cont (new old)
  (declare (type continuation new old))
  (assert (member (continuation-kind new) '(:block-start :unused)))
  (assert (eq (continuation-kind old) :inside-block))

  (let ((use (continuation-use old)))
    (delete-continuation-use use)
    (add-continuation-use use new))

  (undefined-value))
|#


ram's avatar
ram committed
;;; NODE-BLOCK, NODE-ENVIRONMENT, NODE-TLF-NUMBER  --  Interface
wlott's avatar
wlott committed
;;;
;;;    Shorthand for common idiom.
;;;
ram's avatar
ram committed
(proclaim '(inline node-block node-environment node-tlf-number))
wlott's avatar
wlott committed
(defun node-block (node)
  (declare (type node node))
  (the cblock (continuation-block (node-prev node))))
;;;
(defun node-environment (node)
  (declare (type node node))
  (the environment (lambda-environment (block-lambda (node-block node)))))
ram's avatar
ram committed
;;;
(defun node-tlf-number (node)
  (declare (type node node))
  (car (last (node-source-path node))))
wlott's avatar
wlott committed


;;;; Flow/DFO/Component hackery:

;;; Link-Blocks, Unlink-Blocks  --  Interface
;;;
;;;    Join or separate Block1 and Block2.
;;;
(proclaim '(ftype (function (block block) void) link-blocks unlink-blocks))
(defun link-blocks (block1 block2)
  (assert (not (member block2 (block-succ block1))))
  (push block2 (block-succ block1))
  (push block1 (block-pred block2)))
;;;
(defun unlink-blocks (block1 block2)
  (assert (member block2 (block-succ block1)))
  (setf (block-succ block1)
	(delete block2 (block-succ block1)))
  (setf (block-pred block2)
	(delete block1 (block-pred block2))))


;;; Change-Block-Successor  --  Internal
;;;
;;;    Swing the succ/pred link between Block and Old to be between Block and
;;; New.  If Block ends in an IF, then we have to fix up the
;;; consequent/alternative blocks to point to New.
;;;
(defun change-block-successor (block old new)
  (declare (type cblock new old block))
  (unlink-blocks block old)
  (unless (member new (block-succ block))
    (link-blocks block new))
  
  (let ((last (block-last block)))
    (when (if-p last)
      (macrolet ((frob (slot)
		   `(when (eq (,slot last) old)
		      (setf (,slot last) new))))
	(frob if-consequent)
	(frob if-alternative))))
  
  (undefined-value))


;;; Remove-From-DFO  --  Interface
;;;
;;;    Unlink a block from the next/prev chain.  We also null out the
;;; Component.
;;;
(proclaim '(function remove-from-dfo (cblock) void))
(defun remove-from-dfo (block)
  (let ((next (block-next block))
	(prev (block-prev block)))
    (setf (block-component block) nil)
    (setf (block-next prev) next)
    (setf (block-prev next) prev)))

;;; Add-To-DFO  --  Interface
;;;
;;;    Add Block to the next/prev chain following After.  We also set the
;;; Component to be the same as for After.
;;;
(proclaim '(function add-to-dfo (block block) void))
(defun add-to-dfo (block after)
  (let ((next (block-next after)))
    (setf (block-component block) (block-component after))
    (setf (block-next after) block)
    (setf (block-prev block) after)
    (setf (block-next block) next)
    (setf (block-prev next) block)))


;;; Clear-Flags  --  Interface
;;;
;;;    Set the Flag for all the blocks in Component to NIL, except for the head
;;; and tail which are set to T.
;;;
(proclaim '(function clear-flags (component) void))
(defun clear-flags (component)
  (let ((head (component-head component))
	(tail (component-tail component)))
    (setf (block-flag head) t)
    (setf (block-flag tail) t)
    (do-blocks (block component)
      (setf (block-flag block) nil))))


;;; Make-Empty-Component  --  Interface
;;;
;;;    Make a component with no blocks in it.  The Block-Flag is initially true
;;; in the head and tail blocks.
;;;
(proclaim '(function make-empty-component () component))
(defun make-empty-component ()
  (let* ((head (make-block-key :start nil :lambda nil :start-cleanup nil
			       :end-cleanup nil :component nil))
	 (tail (make-block-key :start nil :lambda nil :start-cleanup nil
			       :end-cleanup nil :component nil))
	 (res (make-component :head head  :tail tail)))
    (setf (block-flag head) t)
    (setf (block-flag tail) t)
    (setf (block-component head) res)
    (setf (block-component tail) res)
    (setf (block-next head) tail)
    (setf (block-prev tail) head)
    res))


;;; Node-Ends-Block  --  Interface
;;;
;;;    Makes Node the Last node in its block, splitting the block if necessary.
;;; The new block is added to the DFO immediately following Node's block.
wlott's avatar
wlott committed
;;;
;;;    If the mess-up for one of Block's End-Cleanups is moved into the new
;;; block, then we must adjust the end/start cleanups of the new and old blocks
;;; to reflect the movement of the mess-up.  If any of the old end cleanups
;;; were in the new block, then we scan up from that cleanup trying to find one
;;; that isn't.  When we do, that becomes the new start/end cleanup of the
;;; old/new block.  We set the start/end as a pair, since we don't want anyone
;;; to think that a cleanup is necessary.
;;;
wlott's avatar
wlott committed
(defun node-ends-block (node)
  (declare (type node node))
  (let* ((block (node-block node))
	 (start (node-cont node))
	 (last (block-last block))
	 (last-cont (node-cont last)))
    (unless (eq last node)
      (assert (eq (continuation-kind start) :inside-block))
      (let* ((succ (block-succ block))
	     (cleanup (block-end-cleanup block))
	     (new-block
	      (make-block-key :start start
			      :lambda (block-lambda block)
			      :start-cleanup cleanup
			      :end-cleanup cleanup
			      :component (block-component block)
			      :start-uses (list (continuation-use start))
			      :succ succ :last last)))
	(setf (continuation-kind start) :block-start)
	(dolist (b succ)
	  (setf (block-pred b)
		(cons new-block (remove block (block-pred b)))))
	(setf (block-succ block) ())
	(setf (block-last block) node)
	(link-blocks block new-block)
	(add-to-dfo new-block block)
	
	(do ((cont start (node-cont (continuation-next cont))))
	    ((eq cont last-cont)
	     (when (eq (continuation-kind last-cont) :inside-block)
	       (setf (continuation-block last-cont) new-block)))
	  (setf (continuation-block cont) new-block))

	(let ((start-cleanup (block-start-cleanup block)))
	  (do ((cup (find-enclosing-cleanup cleanup)
		    (find-enclosing-cleanup (cleanup-enclosing cup))))
	      ((null cup))
	    (when (eq (node-block (continuation-use (cleanup-start cup)))
		      new-block)
	      (do ((cup (find-enclosing-cleanup (cleanup-enclosing cup))
			(find-enclosing-cleanup (cleanup-enclosing cup))))
		  ((null cup)
		   (setf (block-end-cleanup block) start-cleanup)
		   (setf (block-start-cleanup new-block) start-cleanup))
		(let ((cb (node-block (continuation-use (cleanup-start cup)))))
		  (unless (eq cb new-block)
		    (setf (block-end-cleanup block) cup)
		    (setf (block-start-cleanup new-block) cup)
		    (return))))
	      (return))))
wlott's avatar
wlott committed
	(setf (block-type-asserted block) t)
	(setf (block-test-modified block) t))))

  (undefined-value))


;;;; Deleting stuff:

;;; Delete-Lambda-Var  --  Internal
;;;
;;;    Deal with deleting the last (read) reference to a lambda-var.  We
;;; iterate over all local calls flushing the corresponding argument, allowing
;;; the computation of the argument to be deleted.
;;;
;;;    The lambda-var may still have some sets, but this doesn't cause too much
;;; difficulty, since we can efficiently implement write-only variables.  We
;;; iterate over the sets, marking their blocks for dead code flushing, since
;;; we can delete sets whose value is unused.
;;;
(defun delete-lambda-var (leaf)
  (declare (type lambda-var leaf))
  (let* ((fun (lambda-var-home leaf))
	 (n (position leaf (lambda-vars fun))))
    (dolist (ref (leaf-refs fun))
      (let* ((cont (node-cont ref))
	     (dest (continuation-dest cont)))
	(when (and (combination-p dest)
		   (eq (basic-combination-fun dest) cont)
		   (eq (basic-combination-kind dest) :local))
	  (let ((args (basic-combination-args dest)))
	    (flush-dest (elt args n))
	    (setf (elt args n) nil))))))

  (dolist (set (lambda-var-sets leaf))
    (setf (block-flush-p (node-block set)) t))

  (undefined-value))


;;; Delete-Lambda  --  Internal
;;;
;;;    Deal with deleting the last reference to a lambda.  Since there is only
;;; one way into a lambda, deleting the last reference to a lambda ensures that
;;; there is no way to reach any of the code in it.  So we just set the
;;; Functional-Kind for Fun and its Lets to :Deleted, causing IR1 optimization
;;; to delete blocks in that lambda.
;;;
;;;    If the function isn't a Let, we unlink the function head and tail from
;;; the component head and tail to indicate that the code is unreachable.  We
;;; also delete the function Component-Lambdas (it won't be there before local
;;; call analysis, but no matter.)
;;;
;;;    If the lambda is an XEP, then we null out the Entry-Function in its
;;; Entry-Function so that people will know that it is not an entry point
;;; anymore.
;;;
(defun delete-lambda (leaf)
  (declare (type clambda leaf))
  (let ((kind (functional-kind leaf)))
    (assert (not (member kind '(:deleted :optional :top-level))))
    (setf (functional-kind leaf) :deleted)
    (dolist (let (lambda-lets leaf))
      (setf (functional-kind let) :deleted))

    (if (or (eq kind :let) (eq kind :mv-let))
	(let ((home (lambda-home leaf)))
	  (setf (lambda-lets home) (delete leaf (lambda-lets home))))
	(let* ((bind-block (node-block (lambda-bind leaf)))
	       (component (block-component bind-block))
	       (return (lambda-return leaf)))
	  (unlink-blocks (component-head component) bind-block)
	  (when return
	    (unlink-blocks (node-block return) (component-tail component)))
	  (setf (component-lambdas component)
		(delete leaf (component-lambdas component)))))

    (when (eq kind :external)
      (let ((fun (functional-entry-function leaf)))
	(setf (functional-entry-function fun) nil)
	(when (optional-dispatch-p fun)
	  (delete-optional-dispatch fun)))))

  (undefined-value))


;;; Delete-Optional-Dispatch  --  Internal
;;;
;;;    Deal with deleting the last reference to an Optional-Dispatch.  We have
;;; to be a bit more careful than with lambdas, since Delete-Ref is used both
;;; before and after local call analysis.  Afterward, all references to
;;; still-existing optional-dispatches have been moved to the XEP, leaving it
;;; with no references at all.  So we look at the XEP to see if an
;;; optional-dispatch is still really being used.  But before local call
;;; analysis, there are no XEPs, and all references are direct.
;;;
;;;    When we do delete the optional-dispatch, we grovel all of its
;;; entry-points, making them be normal lambdas, and then deleting the ones
;;; with no references.  This deletes any e-p lambdas that were either never
;;; referenced, or couldn't be deleted when the last deference was deleted (due
;;; to their :Optional kind.)
;;;
;;; Note that the last optional ep may alias the main entry, so when we process
;;; the main entry, its kind may have been changed to NIL or even converted to
;;; a let.
;;;
(defun delete-optional-dispatch (leaf)
  (declare (type optional-dispatch leaf))
  (let ((entry (functional-entry-function leaf)))
    (unless (and entry (leaf-refs entry))
      (assert (or (not entry) (eq (functional-kind entry) :deleted)))
      (setf (functional-kind leaf) :deleted)

      (flet ((frob (fun)
	       (unless (eq (functional-kind fun) :deleted)
		 (assert (eq (functional-kind fun) :optional))
		 (setf (functional-kind fun) nil)
		 (let ((refs (leaf-refs fun)))
		   (cond ((null refs)
			  (delete-lambda fun))
			 ((null (rest refs))
			  (maybe-let-convert fun)))))))
	
	(dolist (ep (optional-dispatch-entry-points leaf))
	  (frob ep))
	(when (optional-dispatch-more-entry leaf)
	  (frob (optional-dispatch-more-entry leaf)))
	(let ((main (optional-dispatch-main-entry leaf)))
	  (when (eq (functional-kind main) :optional)
	    (frob main))))))

  (undefined-value))


;;; Delete-Ref  --  Interface
;;;
;;;    Do stuff to delete the semantic attachments of a Ref node.  When this
;;; leaves zero or one reference, we do a type dispatch off of the leaf to
;;; determine if a special action is appropriate.
;;;
(defun delete-ref (ref)
  (declare (type ref ref))
  (let* ((leaf (ref-leaf ref))
	 (refs (delete ref (leaf-refs leaf))))
    (setf (leaf-refs leaf) refs)
    
    (cond ((null refs)
	   (typecase leaf
	     (lambda-var (delete-lambda-var leaf))
	     (clambda
	      (ecase (functional-kind leaf)
		((nil :external :let :mv-let :escape :cleanup)
		 (delete-lambda leaf))
		((:deleted :optional))))
	     (optional-dispatch
	      (unless (eq (functional-kind leaf) :deleted)
		(delete-optional-dispatch leaf)))))
	  ((null (rest refs))
	   (typecase leaf
	     (clambda (maybe-let-convert leaf))))))

  (undefined-value))


;;; Delete-Return  --  Interface
;;;
;;;    Do stuff to indicate that the return node Node is being deleted.  We set
;;; the RETURN to NIL and remove the function from its tail set.
;;;
;;;    As a rather random special case, we leave the function in the tail set
;;; when there are uses of the result continuation marked TAIL-P.  This is done
;;; to prevent the tail set from being blown away when the back end deletes the
;;; return because it discovers that all calls are tail-recursive.
wlott's avatar
wlott committed
;;;
(defun delete-return (node)
  (declare (type creturn node))
  (let* ((fun (return-lambda node))
	 (tail-set (lambda-tail-set fun)))
    (assert (lambda-return fun))
    (unless (do-uses (use (return-result node) nil)
	      (when (node-tail-p use) (return t)))
      (setf (tail-set-functions tail-set)
	    (delete fun (tail-set-functions tail-set)))
      (setf (lambda-tail-set fun) nil))
wlott's avatar
wlott committed
    (setf (lambda-return fun) nil))
  (undefined-value))


;;; Flush-Dest  --  Interface
;;;
;;;    This function is called by people who delete nodes; it provides a way to
;;; indicate that the value of a continuation is no longer used.  We null out
;;; the Continuation-Dest, set Block-Flush-P in the blocks containing uses of
;;; Cont and set Component-Reoptimize.
;;;
;;;    If the continuation is :Deleted, then we don't do anything, since all
;;; semantics have already been flushed.  If the continuation is a
;;; :Deleted-Block-Start, then we delete the continuation, since its control
;;; semantics have already been deleted.  Deleting the continuation causes its
;;; uses to be reoptimized.  If the Prev of the use is deleted, then we blow
;;; off reoptimization.
;;;
(defun flush-dest (cont)
  (declare (type continuation cont))
  
  (ecase (continuation-kind cont)
    (:deleted)
    (:deleted-block-start
     (assert (continuation-dest cont))
     (setf (continuation-dest cont) nil)
     (delete-continuation cont))
    ((:inside-block :block-start)
     (assert (continuation-dest cont))
     (setf (continuation-dest cont) nil)
     (setf (component-reoptimize (block-component (continuation-block cont)))
	   t)
     (do-uses (use cont)
       (let ((prev (node-prev use)))
	 (unless (eq (continuation-kind prev) :deleted)
	   (let ((block (continuation-block prev)))
	     (setf (block-flush-p block) t)
	     (setf (block-type-asserted block) t)))))))

  (setf (continuation-%type-check cont) nil)
  
  (undefined-value))


;;; MARK-FOR-DELETION  --  Internal
;;;
;;;    Do a graph walk backward from Block, marking all predecessor blocks with
;;; the DELETE-P flag.
;;;
(defun mark-for-deletion (block)
  (declare (type cblock block))
  (unless (block-delete-p block)
    (setf (block-delete-p block) t)
    (dolist (pred (block-pred block))
      (mark-for-deletion pred)))
  (undefined-value))


;;; DELETE-CONTINUATION  --  Interface
;;;
;;;    Delete Cont, eliminating both control and value semantics.  We set
;;; FLUSH-P and COMPONENT-REOPTIMIZE similarly to in FLUSH-DEST.  Here we must
;;; get the component from the use block, since the continuation may be a
;;; :DELETED-BLOCK-START.
;;;
;;;    If Cont has DEST, then it must be the case that the DEST is unreachable,
;;; since we can't compute the value desired.  In this case, we call
;;; MARK-FOR-DELETION to cause the DEST block and its predecessors to tell
;;; people to ignore them, and to cause them to be deleted eventually.
;;;
(defun delete-continuation (cont)
  (declare (type continuation cont))
  (assert (not (eq (continuation-kind cont) :deleted)))
  
  (do-uses (use cont)
    (let ((prev (node-prev use)))
      (unless (eq (continuation-kind prev) :deleted)
	(let ((block (continuation-block prev)))
	  (setf (block-flush-p block) t)
	  (setf (block-type-asserted block) t)
	  (setf (component-reoptimize (block-component block)) t)))))

  (let ((dest (continuation-dest cont)))
    (when dest
      (let ((block (node-block dest)))
	(unless (block-delete-p block)
	  (mark-for-deletion block)))))
  
  (setf (continuation-kind cont) :deleted)
  (setf (continuation-dest cont) nil)
  (setf (continuation-next cont) nil)
  (setf (continuation-asserted-type cont) *empty-type*)
  (setf (continuation-%derived-type cont) *empty-type*)
  (setf (continuation-use cont) nil)
  (setf (continuation-block cont) nil)
  (setf (continuation-reoptimize cont) nil)
  (setf (continuation-%type-check cont) nil)
  (setf (continuation-info cont) nil)
  
  (undefined-value))


;;; Delete-Block  --  Interface
;;;
;;;    This function does what is necessary to eliminate the code in it from
;;; the IR1 representation.  This involves unlinking it from its predecessors
;;; and successors and deleting various node-specific semantic information.
;;;
;;;    We mark the Start as has having no next and remove the last node from
;;; its Cont's uses.  We also flush the DEST for all continuations whose values
;;; are received by nodes in the block.
;;;
(defun delete-block (block)
  (declare (type cblock block))
  (assert (block-component block) () "Block is already deleted.")
  (setf (block-delete-p block) t)

  (let* ((last (block-last block))
	 (cont (node-cont last)))
    (delete-continuation-use last)
    (if (eq (continuation-kind cont) :unused)
	(delete-continuation cont)
	(reoptimize-continuation cont)))
wlott's avatar
wlott committed

  (dolist (b (block-pred block))
    (unlink-blocks b block))
  (dolist (b (block-succ block))
    (unlink-blocks block b))

  (do-nodes (node cont block)
    (typecase node
      (ref (delete-ref node))
      (basic-combination
       (flush-dest (basic-combination-fun node))
       (dolist (arg (basic-combination-args node))
	 (when arg (flush-dest arg))))
      (cif
       (flush-dest (if-test node)))
      (bind
       (let ((lambda (bind-lambda node)))
	 (unless (eq (functional-kind lambda) :deleted)
	   (assert (member (functional-kind lambda) '(:let :mv-let)))
	   (delete-lambda lambda))))
      (exit
       (let ((value (exit-value node)))
	 (when value
	   (flush-dest value))))
      (creturn
       (flush-dest (return-result node))
       (delete-return node))
      (cset
       (flush-dest (set-value node))
       (let ((var (set-var node)))
	 (setf (basic-var-sets var)
	       (delete node (basic-var-sets var))))))

    (delete-continuation (node-prev node)))

  (remove-from-dfo block)
  (undefined-value))


;;; Unlink-Node  --  Interface
;;;
;;;    Delete a node from a block, deleting the block if there are no nodes
;;; left.  We remove the node from the uses of its CONT, but we don't deal with
;;; cleaning up any type-specific semantic attachments.  If the CONT is :UNUSED
;;; after deleting this use, then we delete CONT.  (Note :UNUSED is not the
;;; same as no uses.  A continuation will only become :UNUSED if it was
;;; :INSIDE-BLOCK before.) 
;;;
;;;    If the node is the last node, there must be exactly one successor.  We
;;; link all of our precedessors to the successor and unlink the block.  In
;;; this case, we return T, otherwise NIL.  If no nodes are left, and the block
;;; is a successor of itself, then we replace the only node with a degenerate
;;; exit node.  This provides a way to represent the bodyless infinite loop,
;;; given the prohibition on empty blocks in IR1.
;;;
(defun unlink-node (node)
  (declare (type node node))
  (let* ((cont (node-cont node))
	 (next (continuation-next cont))
	 (prev (node-prev node))
	 (block (continuation-block prev))
	 (prev-kind (continuation-kind prev))
	 (last (block-last block)))
    
    (unless (eq (continuation-kind cont) :deleted)
      (delete-continuation-use node)
      (when (eq (continuation-kind cont) :unused)
	(assert (not (continuation-dest cont)))
	(delete-continuation cont)))
    
    (setf (block-type-asserted block) t)
    (setf (block-test-modified block) t)

    (cond ((or (eq prev-kind :inside-block)
	       (and (eq prev-kind :block-start)
		    (not (eq node last))))
	   (cond ((eq node last)
		  (setf (block-last block) (continuation-use prev))
		  (setf (continuation-next prev) nil))
		 (t
		  (setf (continuation-next prev) next)
		  (setf (node-prev next) prev)))
	   (setf (node-prev node) nil)
	   nil)
	  (t
	   (assert (eq prev-kind :block-start))
	   (assert (eq node last))
	   (let* ((succ (block-succ block))
		  (next (first succ)))
	     (assert (and succ (null (cdr succ))))
	     (cond
	      ((member block succ)
	       (with-ir1-environment node
		 (let ((exit (make-exit :source (node-source node)))
		       (dummy (make-continuation)))
		   (setf (continuation-next prev) nil)
		   (prev-link exit prev)
		   (add-continuation-use exit dummy)
		   (setf (block-last block) exit)))
	       (setf (node-prev node) nil)
	       nil)
	      (t
	       (assert (eq (find-enclosing-cleanup (block-start-cleanup block))
			   (find-enclosing-cleanup (block-end-cleanup block))))
	       (unlink-blocks block next)
	       (dolist (pred (block-pred block))
		 (change-block-successor pred block next))
	       (remove-from-dfo block)
	       (cond ((continuation-dest prev)
		      (setf (continuation-next prev) nil)
		      (setf (continuation-kind prev) :deleted-block-start))
		     (t
		      (delete-continuation prev)))
	       (setf (node-prev node) nil)
	       t)))))))


;;; NODE-DELETED  --  Interface
;;;
;;;    Return true if NODE has been deleted, false if it is still a valid part
;;; of IR1.
;;;
(defun node-deleted (node)
  (declare (type node node))
  (let ((prev (node-prev node)))
    (and prev
	 (not (eq (continuation-kind prev) :deleted))
	 (let ((block (continuation-block prev)))
	   (and (block-component block)
		(not (block-delete-p block)))))))
  

;;;; Leaf hackery:

;;; Change-Ref-Leaf  --  Interface
;;;
;;;    Change the Leaf that a Ref refers to.
;;;
(defun change-ref-leaf (ref leaf)
  (declare (type ref ref) (type leaf leaf))
  (unless (eq (ref-leaf ref) leaf)
    (push ref (leaf-refs leaf))
    (delete-ref ref)
    (setf (ref-leaf ref) leaf)
    (derive-node-type ref (leaf-type leaf))
    (reoptimize-continuation (node-cont ref)))
  (undefined-value))


;;; Substitute-Leaf  --  Interface
;;;
;;;    Change all Refs for Old-Leaf to New-Leaf.
;;;
(defun substitute-leaf (new-leaf old-leaf)
  (declare (type leaf new-leaf old-leaf))
  (dolist (ref (leaf-refs old-leaf))
    (change-ref-leaf ref new-leaf))
  (undefined-value))


;;; Find-Constant  --  Interface
;;;
;;;    Return a Leaf which represents the specified constant object.  If the
;;; object is not in *constants*, then we create a new constant Leaf and
;;; enter it.
;;;
(defun find-constant (object)
  (or (gethash object *constants*)
      (setf (gethash object *constants*)
	    (make-constant :value object  :name nil
			   :type (ctype-of object)
			   :where-from :defined))))


;;;; Find-NLX-Info  --  Interface
;;;
;;;    If there is a non-local exit noted in Entry's environment that exits to
;;; Cont in that entry, then return it, otherwise return NIL.
;;;
(defun find-nlx-info (entry cont)
  (declare (type entry entry) (type continuation cont))
  (dolist (nlx (environment-nlx-info (node-environment entry)) nil)
    (let* ((cleanup (nlx-info-cleanup nlx))
	   (entry-cleanup (ecase (cleanup-kind cleanup)
			    ((:catch :unwind-protect)
			     (cleanup-enclosing cleanup))
			    (:entry cleanup))))
      (when (and (eq (nlx-info-continuation nlx) cont)
		 (eq (continuation-use (cleanup-start entry-cleanup))
		     entry))
	(return nlx)))))


;;;; Functional hackery:

;;; Main-Entry  --  Interface
;;;
;;;    If Functional is a Lambda, just return it; if it is an
;;; optional-dispatch, return the main-entry.
;;;
(proclaim '(function main-entry (functional) lambda))
(defun main-entry (functional)
  (if (lambda-p functional)
      functional
      (optional-dispatch-main-entry functional)))

;;; Looks-Like-An-MV-Bind  --  Interface
;;;
;;;    Returns true if Functional is a thing that can be treated like MV-Bind
;;; when it appears in an MV-Call.  All fixed arguments must be optional with
;;; null default and no supplied-p.  There must be a rest arg with no
;;; references.
;;;
(proclaim '(function looks-like-an-mv-bind (functional) boolean))
(defun looks-like-an-mv-bind (functional)
  (and (optional-dispatch-p functional)
       (do ((arg (optional-dispatch-arglist functional) (cdr arg)))
	   ((null arg) nil)
	 (let ((info (lambda-var-arg-info (car arg))))
	   (unless info (return nil))
	   (case (arg-info-kind info)
	     (:optional
	      (when (or (arg-info-supplied-p info) (arg-info-default info))
		(return nil)))
	     (:rest
	      (return (and (null (cdr arg)) (null (leaf-refs (car arg))))))
	     (t
	      (return nil)))))))

;;; External-Entry-Point-P  --  Interface
;;;
;;;    Return true if function is an XEP.  This is true of normal XEPs
;;; (:External kind) and top-level lambdas (:Top-Level kind.)
;;;
(defun external-entry-point-p (fun)
  (declare (type functional fun))
  (not (null (member (functional-kind fun) '(:external :top-level)))))


;;; Continuation-Function-Name  --  Interface
;;;
;;;    If Cont's only use is a global function reference, then return the
;;; referenced symbol, otherwise NIL.
;;;
(defun continuation-function-name (cont)
  (declare (type continuation cont))
  (let ((use (continuation-use cont)))
    (if (ref-p use)
	(let ((leaf (ref-leaf use)))
	  (if (and (global-var-p leaf)
		   (eq (global-var-kind leaf) :global-function))
	      (leaf-name leaf)
	      nil))
	nil)))


;;; LET-COMBINATION  --  Interface
;;;