0.pre7.114:
[sbcl.git] / src / compiler / main.lisp
index b1677cb..17a2539 100644 (file)
@@ -1,4 +1,6 @@
-;;;; the top-level interfaces to the compiler
+;;;; the top level interfaces to the compiler, plus some other
+;;;; compiler-related stuff (e.g. CL:CALL-ARGUMENTS-LIMIT) which
+;;;; doesn't obviously belong anywhere else
 
 ;;;; This software is part of the SBCL system. See the README file for
 ;;;; more information.
                  *last-source-form* *last-format-string* *last-format-args*
                  *last-message-count* *lexenv*))
 
-(defvar *byte-compile-default* :maybe
-  #!+sb-doc
-  "the default value for the :BYTE-COMPILE argument to COMPILE-FILE")
-
-(defvar *byte-compile-top-level*
-  #-sb-xc-host t
-  #+sb-xc-host nil ; since the byte compiler isn't supported in cross-compiler
-  #!+sb-doc
-  "Similar to *BYTE-COMPILE-DEFAULT*, but controls the compilation of top-level
-   forms (evaluated at load-time) when the :BYTE-COMPILE argument is :MAYBE
-   (the default.)  When true, we decide to byte-compile.")
-
-;;; default value of the :BYTE-COMPILE argument to the compiler
-(defvar *byte-compile* :maybe)
-
-;;; Bound by COMPILE-COMPONENT to T when byte-compiling, and NIL when
-;;; native compiling. During IR1 conversion this can also be :MAYBE,
-;;; in which case we must look at the policy, see (byte-compiling).
-(defvar *byte-compiling* :maybe)
-(declaim (type (member t nil :maybe) *byte-compile* *byte-compiling*
-              *byte-compile-default*))
-
 (defvar *check-consistency* nil)
 (defvar *all-components*)
 
 ;;; Bind this to a stream to capture various internal debugging output.
-#!+sb-show
 (defvar *compiler-trace-output* nil)
 
 ;;; The current block compilation state. These are initialized to the
 (defvar *entry-points*)
 (declaim (list *entry-points*))
 
-;;; When block compiling, used by PROCESS-FORM to accumulate top-level
+;;; When block compiling, used by PROCESS-FORM to accumulate top level
 ;;; lambdas resulting from compiling subforms. (In reverse order.)
-(defvar *top-level-lambdas*)
-(declaim (list *top-level-lambdas*))
+(defvar *toplevel-lambdas*)
+(declaim (list *toplevel-lambdas*))
 
 (defvar sb!xc:*compile-verbose* t
   #!+sb-doc
               sb!xc:*compile-file-pathname*
               sb!xc:*compile-file-truename*))
 
-;;; the values of *PACKAGE* and policy when compilation started
-(defvar *initial-package*)
-(defvar *initial-cookie*)
-(defvar *initial-interface-cookie*)
-
-;;; The source-info structure for the current compilation. This is null
-;;; globally to indicate that we aren't currently in any identifiable
-;;; compilation.
+;;; the SOURCE-INFO structure for the current compilation. This is
+;;; null globally to indicate that we aren't currently in any
+;;; identifiable compilation.
 (defvar *source-info* nil)
 
-;;; True if we are within a WITH-COMPILATION-UNIT form (which normally
-;;; causes nested uses to be no-ops).
+;;; This is true if we are within a WITH-COMPILATION-UNIT form (which
+;;; normally causes nested uses to be no-ops).
 (defvar *in-compilation-unit* nil)
 
 ;;; Count of the number of compilation units dynamically enclosed by
     (pprint-logical-block (*error-output* nil :per-line-prefix "; ")
        (apply #'compiler-mumble foo))))
 
-(deftype object () '(or fasl-file core-object null))
+(deftype object () '(or fasl-output core-object null))
 
 (defvar *compile-object* nil)
 (declaim (type object *compile-object*))
                                     (if (symbolp x)
                                         (symbol-name x)
                                         (prin1-to-string x)))))))
-       (unless *converting-for-interpreter*
-         (dolist (undef undefs)
-           (let ((name (undefined-warning-name undef))
-                 (kind (undefined-warning-kind undef))
-                 (warnings (undefined-warning-warnings undef))
-                 (undefined-warning-count (undefined-warning-count undef)))
-             (dolist (*compiler-error-context* warnings)
-               (compiler-style-warning "undefined ~(~A~): ~S" kind name))
-
-             (let ((warn-count (length warnings)))
-               (when (and warnings (> undefined-warning-count warn-count))
-                 (let ((more (- undefined-warning-count warn-count)))
-                   (compiler-style-warning
-                    "~D more use~:P of undefined ~(~A~) ~S"
-                    more kind name)))))))
+       (dolist (undef undefs)
+         (let ((name (undefined-warning-name undef))
+               (kind (undefined-warning-kind undef))
+               (warnings (undefined-warning-warnings undef))
+               (undefined-warning-count (undefined-warning-count undef)))
+           (dolist (*compiler-error-context* warnings)
+             (compiler-style-warning "undefined ~(~A~): ~S" kind name))
+           (let ((warn-count (length warnings)))
+             (when (and warnings (> undefined-warning-count warn-count))
+               (let ((more (- undefined-warning-count warn-count)))
+                 (compiler-style-warning
+                  "~W more use~:P of undefined ~(~A~) ~S"
+                  more kind name))))))
        
        (dolist (kind '(:variable :function :type))
          (let ((summary (mapcar #'undefined-warning-name
                ~%  ~{~<~%  ~1:;~S~>~^ ~}"
               (cdr summary) kind summary)))))))
 
-  (unless (or *converting-for-interpreter*
-             (and (not abort-p)
-                  (zerop *aborted-compilation-unit-count*)
-                  (zerop *compiler-error-count*)
-                  (zerop *compiler-warning-count*)
-                  (zerop *compiler-style-warning-count*)
-                  (zerop *compiler-note-count*)))
+  (unless (and (not abort-p)
+              (zerop *aborted-compilation-unit-count*)
+              (zerop *compiler-error-count*)
+              (zerop *compiler-warning-count*)
+              (zerop *compiler-style-warning-count*)
+              (zerop *compiler-note-count*))
     (format *error-output* "~&")
     (pprint-logical-block (*error-output* nil :per-line-prefix "; ")
       (compiler-mumble "compilation unit ~:[finished~;aborted~]~
-                       ~[~:;~:*~&  caught ~D fatal ERROR condition~:P~]~
-                       ~[~:;~:*~&  caught ~D ERROR condition~:P~]~
-                       ~[~:;~:*~&  caught ~D WARNING condition~:P~]~
-                       ~[~:;~:*~&  caught ~D STYLE-WARNING condition~:P~]~
-                       ~[~:;~:*~&  printed ~D note~:P~]"
+                       ~[~:;~:*~&  caught ~W fatal ERROR condition~:P~]~
+                       ~[~:;~:*~&  caught ~W ERROR condition~:P~]~
+                       ~[~:;~:*~&  caught ~W WARNING condition~:P~]~
+                       ~[~:;~:*~&  caught ~W STYLE-WARNING condition~:P~]~
+                       ~[~:;~:*~&  printed ~W note~:P~]"
                       abort-p
                       *aborted-compilation-unit-count*
                       *compiler-error-count*
        (setf (component-reanalyze component) nil))
       (setf (component-reoptimize component) nil)
       (ir1-optimize component)
-      (unless (component-reoptimize component)
-       (maybe-mumble " ")
-       (return))
-      (incf count)
-      (when (= count *max-optimize-iterations*)
-       (event ir1-optimize-maxed-out)
-       (maybe-mumble "* ")
-       (setf (component-reoptimize component) nil)
-       (do-blocks (block component)
-         (setf (block-reoptimize block) nil))
-       (return))
+      (cond ((component-reoptimize component)
+             (incf count)
+             (when (= count *max-optimize-iterations*)
+               (maybe-mumble "*")
+               (cond ((retry-delayed-ir1-transforms :optimize)
+                     (maybe-mumble "+")
+                     (setq count 0))
+                     (t
+                     (event ir1-optimize-maxed-out)
+                     (setf (component-reoptimize component) nil)
+                     (do-blocks (block component)
+                       (setf (block-reoptimize block) nil))
+                     (return)))))
+            ((retry-delayed-ir1-transforms :optimize)
+            (setf count 0)
+            (maybe-mumble "+"))
+           (t
+             (maybe-mumble " ")
+            (return)))
       (maybe-mumble "."))
     (when cleared-reanalyze
       (setf (component-reanalyze component) t)))
   (values))
 
 (defparameter *constraint-propagate* t)
-(defparameter *reoptimize-after-type-check-max* 5)
+
+;;; KLUDGE: This was bumped from 5 to 10 in a DTC patch ported by MNA
+;;; from CMU CL into sbcl-0.6.11.44, the same one which allowed IR1
+;;; transforms to be delayed. Either DTC or MNA or both didn't explain
+;;; why, and I don't know what the rationale was. -- WHN 2001-04-28
+;;;
+;;; FIXME: It would be good to document why it's important to have a
+;;; large value here, and what the drawbacks of an excessively large
+;;; value are; and it might also be good to make it depend on
+;;; optimization policy.
+(defparameter *reoptimize-after-type-check-max* 10)
 
 (defevent reoptimize-maxed-out
   "*REOPTIMIZE-AFTER-TYPE-CHECK-MAX* exceeded.")
 (defun ir1-phases (component)
   (declare (type component component))
   (let ((*constraint-number* 0)
-       (loop-count 1))
-    (declare (special *constraint-number*))
+       (loop-count 1)
+        (*delayed-ir1-transforms* nil))
+    (declare (special *constraint-number* *delayed-ir1-transforms*))
     (loop
       (ir1-optimize-until-done component)
-      (when (or (component-new-functions component)
-               (component-reanalyze-functions component))
+      (when (or (component-new-funs component)
+               (component-reanalyze-funs component))
        (maybe-mumble "locall ")
-       (local-call-analyze component))
+       (locall-analyze-component component))
       (dfo-as-needed component)
       (when *constraint-propagate*
        (maybe-mumble "constraint ")
        (constraint-propagate component))
-      (maybe-mumble "type ")
+      (when (retry-delayed-ir1-transforms :constraint)
+        (maybe-mumble "Rtran "))
       ;; Delay the generation of type checks until the type
       ;; constraints have had time to propagate, else the compiler can
       ;; confuse itself.
       (unless (and (or (component-reoptimize component)
                       (component-reanalyze component)
-                      (component-new-functions component)
-                      (component-reanalyze-functions component))
-                  (< loop-count (- *reoptimize-after-type-check-max* 2)))
+                      (component-new-funs component)
+                      (component-reanalyze-funs component))
+                  (< loop-count (- *reoptimize-after-type-check-max* 4)))
+        (maybe-mumble "type ")
        (generate-type-checks component)
        (unless (or (component-reoptimize component)
                    (component-reanalyze component)
-                   (component-new-functions component)
-                   (component-reanalyze-functions component))
+                   (component-new-funs component)
+                   (component-reanalyze-funs component))
          (return)))
       (when (>= loop-count *reoptimize-after-type-check-max*)
        (maybe-mumble "[reoptimize limit]")
   (ir1-finalize component)
   (values))
 
-(defun native-compile-component (component)
+(defun %compile-component (component)
   (let ((*code-segment* nil)
        (*elsewhere* nil))
     (maybe-mumble "GTN ")
          (entry-analyze component)
          (ir2-convert component)
 
-         (when (policy nil (>= speed cspeed))
+         (when (policy *lexenv* (>= speed compilation-speed))
            (maybe-mumble "copy ")
            (copy-propagate component))
 
            (maybe-mumble "check-pack ")
            (check-pack-consistency component))
 
-         #!+sb-show
          (when *compiler-trace-output*
            (describe-component component *compiler-trace-output*)
            (describe-ir2-component component *compiler-trace-output*))
          (multiple-value-bind (code-length trace-table fixups)
              (generate-code component)
 
-           #!+sb-show
            (when *compiler-trace-output*
              (format *compiler-trace-output*
                      "~|~%disassembly of code for ~S~2%" component)
                                                     *compiler-trace-output*))
 
            (etypecase *compile-object*
-             (fasl-file
+             (fasl-output
               (maybe-mumble "fasl")
               (fasl-dump-component component
                                    *code-segment*
                                    *compile-object*))
              (null))))))
 
-  ;; We are done, so don't bother keeping anything around.
+  ;; We're done, so don't bother keeping anything around.
   (setf (component-info component) nil)
 
   (values))
 
-;;; Return our best guess for whether we will byte compile code
-;;; currently being IR1 converted. This is only a guess because the
-;;; decision is made on a per-component basis.
-;;;
-;;; FIXME: This should be called something more mnemonic, e.g.
-;;; PROBABLY-BYTE-COMPILING
-(defun byte-compiling ()
-  (if (eq *byte-compiling* :maybe)
-      (or (eq *byte-compile* t)
-         (policy nil (zerop speed) (<= debug 1)))
-      (and *byte-compile* *byte-compiling*)))
-
 ;;; Delete components with no external entry points before we try to
-;;; generate code. Unreachable closures can cause IR2 conversion to puke on
-;;; itself, since it is the reference to the closure which normally causes the
-;;; components to be combined. This doesn't really cover all cases...
+;;; generate code. Unreachable closures can cause IR2 conversion to
+;;; puke on itself, since it is the reference to the closure which
+;;; normally causes the components to be combined.
 (defun delete-if-no-entries (component)
-  (dolist (fun (component-lambdas component)
-              (delete-component component))
+  (dolist (fun (component-lambdas component) (delete-component component))
+    (when (functional-has-external-references-p fun)
+      (return))
     (case (functional-kind fun)
-      (:top-level (return))
+      (:toplevel (return))
       (:external
-       (unless (every #'(lambda (ref)
-                         (eq (block-component (node-block ref))
-                             component))
+       (unless (every (lambda (ref)
+                       (eq (block-component (node-block ref))
+                           component))
                      (leaf-refs fun))
         (return))))))
 
 (defun compile-component (component)
-  (let* ((*component-being-compiled* component)
-        (*byte-compiling*
-         (ecase *byte-compile*
-           ((t) t)
-           ((nil) nil)
-           (:maybe
-            (dolist (fun (component-lambdas component) t)
-              (unless (policy (lambda-bind fun)
-                              (zerop speed) (<= debug 1))
-                (return nil)))))))
-
+  (let* ((*component-being-compiled* component))
     (when sb!xc:*compile-print*
-      (compiler-mumble "~&; ~:[~;byte ~]compiling ~A: "
-                      *byte-compiling*
-                      (component-name component)))
+      (compiler-mumble "~&; compiling ~A: " (component-name component)))
 
     (ir1-phases component)
 
     ;; FIXME: What is MAYBE-MUMBLE for? Do we need it any more?
     (maybe-mumble "env ")
-    (environment-analyze component)
+    (physenv-analyze component)
     (dfo-as-needed component)
 
     (delete-if-no-entries component)
 
     (unless (eq (block-next (component-head component))
                (component-tail component))
-      (if *byte-compiling*
-         (byte-compile-component component)
-         (native-compile-component component))))
+      (%compile-component component)))
 
   (clear-constant-info)
 
     (clrhash *id-labels*)
     (setq *label-id* 0)
 
-    ;; Clear some Pack data structures (for GC purposes only).
-    (assert (not *in-pack*))
+    ;; Clear some PACK data structures (for GC purposes only).
+    (aver (not *in-pack*))
     (dolist (sb *backend-sb-list*)
       (when (finite-sb-p sb)
        (fill (finite-sb-live-tns sb) nil))))
 ;;;; Source-Info structure. The bookkeeping is done as a side-effect
 ;;;; of getting the next source form.
 
-;;; The File-Info structure holds all the source information for a
+;;; A FILE-INFO structure holds all the source information for a
 ;;; given file.
-(defstruct file-info
-  ;; If a file, the truename of the corresponding source file. If from a Lisp
-  ;; form, :LISP, if from a stream, :STREAM.
-  (name (required-argument) :type (or pathname (member :lisp :stream)))
-  ;; The defaulted, but not necessarily absolute file name (i.e. prior to
-  ;; TRUENAME call.)  Null if not a file. This is used to set
-  ;; *COMPILE-FILE-PATHNAME*, and if absolute, is dumped in the debug-info.
+(defstruct (file-info (:copier nil))
+  ;; If a file, the truename of the corresponding source file. If from
+  ;; a Lisp form, :LISP. If from a stream, :STREAM.
+  (name (missing-arg) :type (or pathname (member :lisp :stream)))
+  ;; the defaulted, but not necessarily absolute file name (i.e. prior
+  ;; to TRUENAME call.) Null if not a file. This is used to set
+  ;; *COMPILE-FILE-PATHNAME*, and if absolute, is dumped in the
+  ;; debug-info.
   (untruename nil :type (or pathname null))
-  ;; The file's write date (if relevant.)
+  ;; the file's write date (if relevant)
   (write-date nil :type (or unsigned-byte null))
-  ;; The source path root number of the first form in this file (i.e. the
-  ;; total number of forms converted previously in this compilation.)
+  ;; the source path root number of the first form in this file (i.e.
+  ;; the total number of forms converted previously in this
+  ;; compilation)
   (source-root 0 :type unsigned-byte)
-  ;; Parallel vectors containing the forms read out of the file and the file
-  ;; positions that reading of each form started at (i.e. the end of the
-  ;; previous form.)
+  ;; parallel vectors containing the forms read out of the file and
+  ;; the file positions that reading of each form started at (i.e. the
+  ;; end of the previous form)
   (forms (make-array 10 :fill-pointer 0 :adjustable t) :type (vector t))
   (positions (make-array 10 :fill-pointer 0 :adjustable t) :type (vector t)))
 
 (defstruct (source-info
            #-no-ansi-print-object
            (:print-object (lambda (s stream)
-                            (print-unreadable-object (s stream :type t)))))
+                            (print-unreadable-object (s stream :type t))))
+           (:copier nil))
   ;; the UT that compilation started at
   (start-time (get-universal-time) :type unsigned-byte)
-  ;; a list of the FILE-INFO structures for this compilation
-  (files nil :type list)
-  ;; the tail of the FILES for the file we are currently reading
-  (current-file nil :type list)
-  ;; the stream that we are using to read the CURRENT-FILE, or NIL if
+  ;; the FILE-INFO structure for this compilation
+  (file-info nil :type (or file-info null))
+  ;; the stream that we are using to read the FILE-INFO, or NIL if
   ;; no stream has been opened yet
   (stream nil :type (or stream null)))
 
-;;; Given a list of pathnames, return a SOURCE-INFO structure.
-(defun make-file-source-info (files)
-  (declare (list files))
-  (let ((file-info
-        (mapcar (lambda (x)
-                  (make-file-info :name (truename x)
-                                  :untruename x
-                                  :write-date (file-write-date x)))
-                files)))
-
-    (make-source-info :files file-info
-                     :current-file file-info)))
-
-;;; Return a SOURCE-INFO to describe the incremental compilation of
-;;; FORM. Also used by SB!EVAL:INTERNAL-EVAL.
-(defun make-lisp-source-info (form)
-  (make-source-info
-   :start-time (get-universal-time)
-   :files (list (make-file-info :name :lisp
-                               :forms (vector form)
-                               :positions '#(0)))))
+;;; Given a pathname, return a SOURCE-INFO structure.
+(defun make-file-source-info (file)
+  (let ((file-info (make-file-info :name (truename file)
+                                  :untruename file
+                                  :write-date (file-write-date file))))
 
-;;; Return a SOURCE-INFO which will read from Stream.
-(defun make-stream-source-info (stream)
-  (let ((files (list (make-file-info :name :stream))))
-    (make-source-info
-     :files files
-     :current-file files
-     :stream stream)))
-
-;;; Print an error message for a non-EOF error on STREAM. OLD-POS is a
-;;; preceding file position that hopefully comes before the beginning
-;;; of the line. Of course, this only works on streams that support
-;;; the file-position operation.
-(defun normal-read-error (stream old-pos condition)
-  (declare (type stream stream) (type unsigned-byte old-pos))
-  (let ((pos (file-position stream)))
-    (file-position stream old-pos)
-    (let ((start old-pos))
-      (loop
-       (let ((line (read-line stream nil))
-             (end (file-position stream)))
-         (when (>= end pos)
-           ;; FIXME: READER-ERROR also prints the file position. Do we really
-           ;; need to try to give position information here?
-           (compiler-abort "read error at ~D:~% \"~A/\\~A\"~%~A"
-                           pos
-                           (string-left-trim "         "
-                                             (subseq line 0 (- pos start)))
-                           (subseq line (- pos start))
-                           condition)
-           (return))
-         (setq start end)))))
-  (values))
+    (make-source-info :file-info file-info)))
 
-;;; Back STREAM up to the position Pos, then read a form with
-;;; *READ-SUPPRESS* on, discarding the result. If an error happens
-;;; during this read, then bail out using COMPILER-ERROR (fatal in
-;;; this context).
-(defun ignore-error-form (stream pos)
-  (declare (type stream stream) (type unsigned-byte pos))
-  (file-position stream pos)
-  (handler-case (let ((*read-suppress* t))
-                 (read stream))
-    (error (condition)
-      (declare (ignore condition))
-      (compiler-error "unable to recover from read error"))))
-
-;;; Print an error message giving some context for an EOF error. We
-;;; print the first line after POS that contains #\" or #\(, or
-;;; lacking that, the first non-empty line.
-(defun unexpected-eof-error (stream pos condition)
-  (declare (type stream stream) (type unsigned-byte pos))
-  (let ((res nil))
-    (file-position stream pos)
-    (loop
-      (let ((line (read-line stream nil nil)))
-       (unless line (return))
-       (when (or (find #\" line) (find #\( line))
-         (setq res line)
-         (return))
-       (unless (or res (zerop (length line)))
-         (setq res line))))
-    (compiler-abort "read error in form starting at ~D:~%~@[ \"~A\"~%~]~A"
-                   pos
-                   res
-                   condition))
-  (file-position stream (file-length stream))
-  (values))
+;;; Return a SOURCE-INFO to describe the incremental compilation of FORM. 
+(defun make-lisp-source-info (form)
+  (make-source-info :start-time (get-universal-time)
+                   :file-info (make-file-info :name :lisp
+                                              :forms (vector form)
+                                              :positions '#(0))))
 
-;;; Read a form from STREAM, returning EOF at EOF. If a read error
-;;; happens, then attempt to recover if possible, returning a proxy
-;;; error form.
-;;;
-;;; FIXME: This seems like quite a lot of complexity, and it seems
-;;; impossible to get it quite right. (E.g. the `(CERROR ..) form
-;;; returned here won't do the right thing if it's not in a position
-;;; for an executable form.) I think it might be better to just stop
-;;; trying to recover from read errors, punting all this noise
-;;; (including UNEXPECTED-EOF-ERROR and IGNORE-ERROR-FORM) and doing a
-;;; COMPILER-ABORT instead.
-(defun careful-read (stream eof pos)
-  (handler-case (read stream nil eof)
-    (error (condition)
-      (let ((new-pos (file-position stream)))
-       (cond ((= new-pos (file-length stream))
-              (unexpected-eof-error stream pos condition))
-             (t
-              (normal-read-error stream pos condition)
-              (ignore-error-form stream pos))))
-      '(cerror "Skip this form."
-              "compile-time read error"))))
-
-;;; If Stream is present, return it, otherwise open a stream to the
-;;; current file. There must be a current file. When we open a new
-;;; file, we also reset *PACKAGE* and policy. This gives the effect of
-;;; rebinding around each file.
+;;; Return a SOURCE-INFO which will read from STREAM.
+(defun make-stream-source-info (stream)
+  (let ((file-info (make-file-info :name :stream)))
+    (make-source-info :file-info file-info
+                     :stream stream)))
+
+;;; Return a form read from STREAM; or for EOF use the trick,
+;;; popularized by Kent Pitman, of returning STREAM itself. If an
+;;; error happens, then convert it to standard abort-the-compilation
+;;; error condition (possibly recording some extra location
+;;; information).
+(defun read-for-compile-file (stream position)
+  (handler-case (read stream nil stream)
+    (reader-error (condition)
+     (error 'input-error-in-compile-file
+           :error condition
+           ;; We don't need to supply :POSITION here because
+           ;; READER-ERRORs already know their position in the file.
+           ))
+    ;; ANSI, in its wisdom, says that READ should return END-OF-FILE
+    ;; (and that this is not a READER-ERROR) when it encounters end of
+    ;; file in the middle of something it's trying to read.
+    (end-of-file (condition)
+     (error 'input-error-in-compile-file
+           :error condition
+           ;; We need to supply :POSITION here because the END-OF-FILE
+           ;; condition doesn't carry the position that the user
+           ;; probably cares about, where the failed READ began.
+           :position position))))
+
+;;; If STREAM is present, return it, otherwise open a stream to the
+;;; current file. There must be a current file.
 ;;;
-;;; FIXME: Since we now do the standard ANSI thing of only one file
-;;; per compile (unlike the CMU CL extended COMPILE-FILE) can't this
-;;; complexity (including ADVANCE-SOURCE-FILE) go away?
+;;; FIXME: This is probably an unnecessarily roundabout way to do
+;;; things now that we process a single file in COMPILE-FILE (unlike
+;;; the old CMU CL code, which accepted multiple files). Also, the old
+;;; comment said
+;;;   When we open a new file, we also reset *PACKAGE* and policy.
+;;;   This gives the effect of rebinding around each file.
+;;; which doesn't seem to be true now. Check to make sure that if
+;;; such rebinding is necessary, it's still done somewhere.
 (defun get-source-stream (info)
   (declare (type source-info info))
-  (cond ((source-info-stream info))
-       (t
-        (setq *package* *initial-package*)
-        (setq *default-cookie* (copy-cookie *initial-cookie*))
-        (setq *default-interface-cookie*
-              (copy-cookie *initial-interface-cookie*))
-        (let* ((finfo (first (source-info-current-file info)))
-               (name (file-info-name finfo)))
-          (setq sb!xc:*compile-file-truename* name)
-          (setq sb!xc:*compile-file-pathname* (file-info-untruename finfo))
-          (setf (source-info-stream info)
-                (open name :direction :input))))))
+  (or (source-info-stream info)
+      (let* ((file-info (source-info-file-info info))
+            (name (file-info-name file-info)))
+       (setf sb!xc:*compile-file-truename* name
+             sb!xc:*compile-file-pathname* (file-info-untruename file-info)
+             (source-info-stream info) (open name :direction :input)))))
 
 ;;; Close the stream in INFO if it is open.
 (defun close-source-info (info)
   (setf (source-info-stream info) nil)
   (values))
 
-;;; Advance INFO to the next source file. If there is no next source
-;;; file, return NIL, otherwise T.
-(defun advance-source-file (info)
-  (declare (type source-info info))
-  (close-source-info info)
-  (let ((prev (pop (source-info-current-file info))))
-    (if (source-info-current-file info)
-       (let ((current (first (source-info-current-file info))))
-         (setf (file-info-source-root current)
-               (+ (file-info-source-root prev)
-                  (length (file-info-forms prev))))
-         t)
-       nil)))
-
-;;; Read the sources from the source files and process them.
-(defun process-sources (info)
-  (let* ((file (first (source-info-current-file info)))
+;;; Read and compile the source file.
+(defun sub-sub-compile-file (info)
+  (let* ((file-info (source-info-file-info info))
         (stream (get-source-stream info)))
     (loop
      (let* ((pos (file-position stream))
-           (eof '(*eof*))
-           (form (careful-read stream eof pos)))
-       (if (eq form eof)
-        (return)
-        (let* ((forms (file-info-forms file))
-               (current-idx (+ (fill-pointer forms)
-                               (file-info-source-root file))))
-          (vector-push-extend form forms)
-          (vector-push-extend pos (file-info-positions file))
-          (clrhash *source-paths*)
-          (find-source-paths form current-idx)
-          (process-top-level-form form
-                                  `(original-source-start 0 ,current-idx))))))
-    (when (advance-source-file info)
-      (process-sources info))))
-
-;;; Return the FILE-INFO describing the INDEX'th form.
-(defun find-file-info (index info)
-  (declare (type index index) (type source-info info))
-  (dolist (file (source-info-files info))
-    (when (> (+ (length (file-info-forms file))
-               (file-info-source-root file))
-            index)
-      (return file))))
+           (form (read-for-compile-file stream pos)))
+       (if (eq form stream) ; i.e., if EOF
+          (return)
+          (let* ((forms (file-info-forms file-info))
+                 (current-idx (+ (fill-pointer forms)
+                                 (file-info-source-root file-info))))
+            (vector-push-extend form forms)
+            (vector-push-extend pos (file-info-positions file-info))
+            (find-source-paths form current-idx)
+            (process-toplevel-form form
+                                   `(original-source-start 0 ,current-idx)
+                                   nil)))))))
 
 ;;; Return the INDEX'th source form read from INFO and the position
 ;;; where it was read.
 (defun find-source-root (index info)
-  (declare (type source-info info) (type index index))
-  (let* ((file (find-file-info index info))
-        (idx (- index (file-info-source-root file))))
-    (values (aref (file-info-forms file) idx)
-           (aref (file-info-positions file) idx))))
+  (declare (type index index) (type source-info info))
+  (let ((file-info (source-info-file-info info)))
+    (values (aref (file-info-forms file-info) index)
+           (aref (file-info-positions file-info) index))))
 \f
-;;;; top-level form processing
+;;;; processing of top level forms
 
-;;; This is called by top-level form processing when we are ready to
+;;; This is called by top level form processing when we are ready to
 ;;; actually compile something. If *BLOCK-COMPILE* is T, then we still
 ;;; convert the form, but delay compilation, pushing the result on
-;;; *TOP-LEVEL-LAMBDAS* instead.
+;;; *TOPLEVEL-LAMBDAS* instead.
 (defun convert-and-maybe-compile (form path)
   (declare (list path))
-  (let* ((*lexenv* (make-lexenv :cookie *default-cookie*
-                               :interface-cookie *default-interface-cookie*))
-        (tll (ir1-top-level form path nil)))
-    (cond ((eq *block-compile* t) (push tll *top-level-lambdas*))
-         (t (compile-top-level (list tll) nil)))))
-
-;;; Process a PROGN-like portion of a top-level form. Forms is a list of
-;;; the forms, and Path is source path of the form they came out of.
-(defun process-top-level-progn (forms path)
-  (declare (list forms) (list path))
-  (dolist (form forms)
-    (process-top-level-form form path)))
+  (let* ((*lexenv* (make-lexenv :policy *policy*))
+        (tll (ir1-toplevel form path nil)))
+    (cond ((eq *block-compile* t) (push tll *toplevel-lambdas*))
+         (t (compile-toplevel (list tll) nil)))))
 
-;;; Macroexpand form in the current environment with an error handler.
+;;; Macroexpand FORM in the current environment with an error handler.
 ;;; We only expand one level, so that we retain all the intervening
 ;;; forms in the source path.
-(defun preprocessor-macroexpand (form)
+(defun preprocessor-macroexpand-1 (form)
   (handler-case (sb!xc:macroexpand-1 form *lexenv*)
     (error (condition)
-       (compiler-error "(during macroexpansion)~%~A" condition))))
+      (compiler-error "(during macroexpansion of ~A)~%~A"
+                     (let ((*print-level* 1)
+                           (*print-length* 2))
+                       (format nil "~S" form))
+                     condition))))
+
+;;; Process a PROGN-like portion of a top level form. FORMS is a list of
+;;; the forms, and PATH is the source path of the FORM they came out of.
+;;; COMPILE-TIME-TOO is as in ANSI "3.2.3.1 Processing of Top Level Forms".
+(defun process-toplevel-progn (forms path compile-time-too)
+  (declare (list forms) (list path))
+  (dolist (form forms)
+    (process-toplevel-form form path compile-time-too)))
 
-;;; Process a top-level use of LOCALLY. We parse declarations and then
-;;; recursively process the body.
-;;;
-;;; Binding *DEFAULT-xxx-COOKIE* is pretty much of a hack, since it
-;;; causes LOCALLY to "capture" enclosed proclamations. It is
-;;; necessary because CONVERT-AND-MAYBE-COMPILE uses the value of
-;;; *DEFAULT-COOKIE* as the policy. The need for this hack is due to
-;;; the quirk that there is no way to represent in a cookie that an
-;;; optimize quality came from the default.
-(defun process-top-level-locally (form path)
+;;; Process a top level use of LOCALLY, or anything else (e.g.
+;;; MACROLET) at top level which has declarations and ordinary forms.
+;;; We parse declarations and then recursively process the body.
+(defun process-toplevel-locally (body path compile-time-too)
   (declare (list path))
-  (multiple-value-bind (forms decls) (sb!sys:parse-body (cdr form) nil)
+  (multiple-value-bind (forms decls) (sb!sys:parse-body body nil)
     (let* ((*lexenv*
            (process-decls decls nil nil (make-continuation)))
-          (*default-cookie* (lexenv-cookie *lexenv*))
-          (*default-interface-cookie* (lexenv-interface-cookie *lexenv*)))
-      (process-top-level-progn forms path))))
-
-;;; Force any pending top-level forms to be compiled and dumped so
-;;; that they will be evaluated in the correct package environment.
-;;; Dump the form to be evaled at (cold) load time, and if EVAL is
-;;; true, eval the form immediately.
-(defun process-cold-load-form (form path eval)
-  (let ((object *compile-object*))
-    (etypecase object
-      (fasl-file
-       (compile-top-level-lambdas () t)
-       (fasl-dump-cold-load-form form object))
-      ((or null core-object)
-       (convert-and-maybe-compile form path)))
-    (when eval
-      (eval form))))
-
-(declaim (special *compiler-error-bailout*))
-
-;;; Process a top-level FORM with the specified source PATH.
-;;;  * If this is a magic top-level form, then do stuff.
+          ;; Binding *POLICY* is pretty much of a hack, since it
+          ;; causes LOCALLY to "capture" enclosed proclamations. It
+          ;; is necessary because CONVERT-AND-MAYBE-COMPILE uses the
+          ;; value of *POLICY* as the policy. The need for this hack
+          ;; is due to the quirk that there is no way to represent in
+          ;; a POLICY that an optimize quality came from the default.
+          ;;
+          ;; FIXME: Ideally, something should be done so that DECLAIM
+          ;; inside LOCALLY works OK. Failing that, at least we could
+          ;; issue a warning instead of silently screwing up.
+          (*policy* (lexenv-policy *lexenv*)))
+      (process-toplevel-progn forms path compile-time-too))))
+
+;;; Parse an EVAL-WHEN situations list, returning three flags,
+;;; (VALUES COMPILE-TOPLEVEL LOAD-TOPLEVEL EXECUTE), indicating
+;;; the types of situations present in the list.
+(defun parse-eval-when-situations (situations)
+  (when (or (not (listp situations))
+           (set-difference situations
+                           '(:compile-toplevel
+                             compile
+                             :load-toplevel
+                             load
+                             :execute
+                             eval)))
+    (compiler-error "bad EVAL-WHEN situation list: ~S" situations))
+  (let ((deprecated-names (intersection situations '(compile load eval))))
+    (when deprecated-names
+      (style-warn "using deprecated EVAL-WHEN situation names~{ ~S~}"
+                 deprecated-names)))
+  (values (intersection '(:compile-toplevel compile)
+                       situations)
+         (intersection '(:load-toplevel load) situations)
+         (intersection '(:execute eval) situations)))
+
+
+;;; utilities for extracting COMPONENTs of FUNCTIONALs
+(defun functional-components (f)
+  (declare (type functional f))
+  (etypecase f
+    (clambda (list (lambda-component f)))
+    (optional-dispatch (let ((result nil))
+                        (labels ((frob (clambda)
+                                   (pushnew (lambda-component clambda)
+                                            result))
+                                 (maybe-frob (maybe-clambda)
+                                   (when maybe-clambda
+                                     (frob maybe-clambda))))
+                          (mapc #'frob (optional-dispatch-entry-points f))
+                          (maybe-frob (optional-dispatch-more-entry f))
+                          (maybe-frob (optional-dispatch-main-entry f)))))))
+
+(defun make-functional-from-toplevel-lambda (definition
+                                            &key
+                                            name
+                                            (path
+                                             ;; I'd thought NIL should
+                                             ;; work, but it doesn't.
+                                             ;; -- WHN 2001-09-20
+                                             (missing-arg)))
+  (let* ((*current-path* path)
+         (component (make-empty-component))
+         (*current-component* component))
+    (setf (component-name component)
+         (debug-namify "~S initial component" name))
+    (setf (component-kind component) :initial)
+    (let* ((locall-fun (ir1-convert-lambda
+                       definition
+                       :debug-name (debug-namify "top level local call ~S"
+                                                 name)))
+           (fun (ir1-convert-lambda (make-xep-lambda-expression locall-fun)
+                                   :source-name (or name '.anonymous.)
+                                   :debug-name (unless name
+                                                 "top level form"))))
+      (setf (functional-entry-fun fun) locall-fun
+            (functional-kind fun) :external
+            (functional-has-external-references-p fun) t)
+      fun)))
+
+;;; Compile LAMBDA-EXPRESSION into *COMPILE-OBJECT*, returning a
+;;; description of the result.
+;;;   * If *COMPILE-OBJECT* is a CORE-OBJECT, then write the function
+;;;     into core and return the compiled FUNCTION value.
+;;;   * If *COMPILE-OBJECT* is a fasl file, then write the function
+;;;     into the fasl file and return a dump handle.
+;;;
+;;; If NAME is provided, then we try to use it as the name of the
+;;; function for debugging/diagnostic information.
+(defun %compile (lambda-expression
+                *compile-object*
+                &key
+                name
+                (path
+                 ;; This magical idiom seems to be the appropriate
+                 ;; path for compiling standalone LAMBDAs, judging
+                 ;; from the CMU CL code and experiment, so it's a
+                 ;; nice default for things where we don't have a
+                 ;; real source path (as in e.g. inside CL:COMPILE).
+                 '(original-source-start 0 0)))
+  (unless (or (null name) (legal-fun-name-p name))
+    (error "not a legal function name: ~S" name))
+  (let* ((*lexenv* (make-lexenv :policy *policy*))
+         (fun (make-functional-from-toplevel-lambda lambda-expression
+                                                   :name name
+                                                   :path path)))
+
+    ;; FIXME: The compile-it code from here on is sort of a
+    ;; twisted version of the code in COMPILE-TOPLEVEL. It'd be
+    ;; better to find a way to share the code there; or
+    ;; alternatively, to use this code to replace the code there.
+    ;; (The second alternative might be pretty easy if we used
+    ;; the :LOCALL-ONLY option to IR1-FOR-LAMBDA. Then maybe the
+    ;; whole FUNCTIONAL-KIND=:TOPLEVEL case could go away..)
+
+    (locall-analyze-clambdas-until-done (list fun))
+    
+    (multiple-value-bind (components-from-dfo top-components hairy-top)
+        (find-initial-dfo (list fun))
+
+      (let ((*all-components* (append components-from-dfo top-components)))
+       ;; FIXME: This is more monkey see monkey do based on CMU CL
+       ;; code. If anyone figures out why to only prescan HAIRY-TOP
+       ;; and TOP-COMPONENTS here, instead of *ALL-COMPONENTS* or
+       ;; some other combination of results from FIND-INITIAL-VALUES,
+       ;; it'd be good to explain it.
+       (mapc #'preallocate-physenvs-for-toplevelish-lambdas hairy-top)
+       (mapc #'preallocate-physenvs-for-toplevelish-lambdas top-components)
+        (dolist (component-from-dfo components-from-dfo)
+          (compile-component component-from-dfo)
+          (replace-toplevel-xeps component-from-dfo)))
+
+      (prog1
+          (let ((entry-table (etypecase *compile-object*
+                               (fasl-output (fasl-output-entry-table
+                                             *compile-object*))
+                               (core-object (core-object-entry-table
+                                             *compile-object*)))))
+            (multiple-value-bind (result found-p)
+                (gethash (leaf-info fun) entry-table)
+              (aver found-p)
+              result))
+        (mapc #'clear-ir1-info components-from-dfo)
+        (clear-stuff)))))
+
+(defun process-toplevel-cold-fset (name lambda-expression path)
+  (unless (producing-fasl-file)
+    (error "can't COLD-FSET except in a fasl file"))
+  (unless (legal-fun-name-p name)
+    (error "not a legal function name: ~S" name))
+  (fasl-dump-cold-fset name
+                       (%compile lambda-expression
+                                 *compile-object*
+                                 :name name
+                                :path path)
+                       *compile-object*)
+  (values))
+
+;;; Process a top level FORM with the specified source PATH.
+;;;  * If this is a magic top level form, then do stuff.
 ;;;  * If this is a macro, then expand it.
 ;;;  * Otherwise, just compile it.
-(defun process-top-level-form (form path)
+;;;
+;;; COMPILE-TIME-TOO is as defined in ANSI
+;;; "3.2.3.1 Processing of Top Level Forms".
+(defun process-toplevel-form (form path compile-time-too)
 
   (declare (list path))
 
-  (catch 'process-top-level-form-error-abort
+  (catch 'process-toplevel-form-error-abort
     (let* ((path (or (gethash form *source-paths*) (cons form path)))
           (*compiler-error-bailout*
-           #'(lambda ()
-               (convert-and-maybe-compile
-                `(error "execution of a form compiled with errors:~% ~S"
-                        ',form)
-                path)
-               (throw 'process-top-level-form-error-abort nil))))
+           (lambda ()
+             (convert-and-maybe-compile
+              `(error "execution of a form compiled with errors:~% ~S"
+                      ',form)
+              path)
+             (throw 'process-toplevel-form-error-abort nil))))
+
       (if (atom form)
+         ;; (There are no EVAL-WHEN issues in the ATOM case until
+         ;; SBCL gets smart enough to handle global
+         ;; DEFINE-SYMBOL-MACRO.)
          (convert-and-maybe-compile form path)
-         (case (car form)
-           ;; FIXME: It's not clear to me why we would want this
-           ;; special case; it might have been needed for some
-           ;; variation of the old GENESIS system, but it certainly
-           ;; doesn't seem to be needed for ours. Sometime after the
-           ;; system is running I'd like to remove it tentatively and
-           ;; see whether anything breaks, and if nothing does break,
-           ;; remove it permanently. (And if we *do* want special
-           ;; treatment of all these, we probably want to treat WARN
-           ;; the same way..)
-           ((error cerror break signal)
-            (process-cold-load-form form path nil))
-           ;; FIXME: ANSI seems to encourage things like DEFSTRUCT to
-           ;; be done with EVAL-WHEN, without this kind of one-off
-           ;; compiler magic.
-           (sb!kernel:%compiler-defstruct
-            (convert-and-maybe-compile form path)
-            (compile-top-level-lambdas () t))
-           ((eval-when)
-            (unless (>= (length form) 2)
-              (compiler-error "EVAL-WHEN form is too short: ~S" form))
-            (do-eval-when-stuff
-             (cadr form) (cddr form)
-             #'(lambda (forms)
-                 (process-top-level-progn forms path))))
-           ((macrolet)
-            (unless (>= (length form) 2)
-              (compiler-error "MACROLET form is too short: ~S" form))
-            (do-macrolet-stuff
-             (cadr form)
-             #'(lambda ()
-                 (process-top-level-progn (cddr form) path))))
-           (locally (process-top-level-locally form path))
-           (progn (process-top-level-progn (cdr form) path))
-           (t
-            (let* ((uform (uncross form))
-                   (exp (preprocessor-macroexpand uform)))
-              (if (eq exp uform)
-                  (convert-and-maybe-compile uform path)
-                  (process-top-level-form exp path))))))))
+         (flet ((need-at-least-one-arg (form)
+                  (unless (cdr form)
+                    (compiler-error "~S form is too short: ~S"
+                                    (car form)
+                                    form))))
+           (case (car form)
+             ;; In the cross-compiler, top level COLD-FSET arranges
+             ;; for static linking at cold init time.
+             #+sb-xc-host
+             ((cold-fset)
+              (aver (not compile-time-too))
+              (destructuring-bind (cold-fset fun-name lambda-expression) form
+                (declare (ignore cold-fset))
+                (process-toplevel-cold-fset fun-name
+                                            lambda-expression
+                                            path)))
+             ((eval-when macrolet symbol-macrolet);things w/ 1 arg before body
+              (need-at-least-one-arg form)
+              (destructuring-bind (special-operator magic &rest body) form
+                (ecase special-operator
+                  ((eval-when)
+                   ;; CT, LT, and E here are as in Figure 3-7 of ANSI
+                   ;; "3.2.3.1 Processing of Top Level Forms".
+                   (multiple-value-bind (ct lt e)
+                       (parse-eval-when-situations magic)
+                     (let ((new-compile-time-too (or ct
+                                                     (and compile-time-too
+                                                          e))))
+                       (cond (lt (process-toplevel-progn
+                                  body path new-compile-time-too))
+                             (new-compile-time-too (eval
+                                                    `(progn ,@body)))))))
+                  ((macrolet)
+                   (funcall-in-macrolet-lexenv
+                    magic
+                    (lambda ()
+                      (process-toplevel-locally body
+                                                path
+                                                compile-time-too))))
+                  ((symbol-macrolet)
+                   (funcall-in-symbol-macrolet-lexenv
+                    magic
+                    (lambda ()
+                      (process-toplevel-locally body
+                                                path
+                                                compile-time-too)))))))
+             ((locally)
+              (process-toplevel-locally (rest form) path compile-time-too))
+             ((progn)
+              (process-toplevel-progn (rest form) path compile-time-too))
+             ;; When we're cross-compiling, consider: what should we
+             ;; do when we hit e.g.
+             ;;   (EVAL-WHEN (:COMPILE-TOPLEVEL)
+             ;;     (DEFUN FOO (X) (+ 7 X)))?
+             ;; DEFUN has a macro definition in the cross-compiler,
+             ;; and a different macro definition in the target
+             ;; compiler. The only sensible thing is to use the
+             ;; target compiler's macro definition, since the
+             ;; cross-compiler's macro is in general into target
+             ;; functions which can't meaningfully be executed at
+             ;; cross-compilation time. So make sure we do the EVAL
+             ;; here, before we macroexpand.
+             ;;
+             ;; Then things get even dicier with something like
+             ;;   (DEFCONSTANT-EQX SB!XC:LAMBDA-LIST-KEYWORDS ..)
+             ;; where we have to make sure that we don't uncross
+             ;; the SB!XC: prefix before we do EVAL, because otherwise
+             ;; we'd be trying to redefine the cross-compilation host's
+             ;; constants.
+             ;;
+             ;; (Isn't it fun to cross-compile Common Lisp?:-)
+             #+sb-xc-host
+             (t
+              (when compile-time-too
+                (eval form)) ; letting xc host EVAL do its own macroexpansion
+              (let* (;; (We uncross the operator name because things
+                     ;; like SB!XC:DEFCONSTANT and SB!XC:DEFTYPE
+                     ;; should be equivalent to their CL: counterparts
+                     ;; when being compiled as target code. We leave
+                     ;; the rest of the form uncrossed because macros
+                     ;; might yet expand into EVAL-WHEN stuff, and
+                     ;; things inside EVAL-WHEN can't be uncrossed
+                     ;; until after we've EVALed them in the
+                     ;; cross-compilation host.)
+                     (slightly-uncrossed (cons (uncross (first form))
+                                               (rest form)))
+                     (expanded (preprocessor-macroexpand-1
+                                slightly-uncrossed)))
+                (if (eq expanded slightly-uncrossed)
+                    ;; (Now that we're no longer processing toplevel
+                    ;; forms, and hence no longer need to worry about
+                    ;; EVAL-WHEN, we can uncross everything.)
+                    (convert-and-maybe-compile expanded path)
+                    ;; (We have to demote COMPILE-TIME-TOO to NIL
+                    ;; here, no matter what it was before, since
+                    ;; otherwise we'd tend to EVAL subforms more than
+                    ;; once, because of WHEN COMPILE-TIME-TOO form
+                    ;; above.)
+                    (process-toplevel-form expanded path nil))))
+             ;; When we're not cross-compiling, we only need to
+             ;; macroexpand once, so we can follow the 1-thru-6
+             ;; sequence of steps in ANSI's "3.2.3.1 Processing of
+             ;; Top Level Forms".
+             #-sb-xc-host
+             (t
+              (let ((expanded (preprocessor-macroexpand-1 form)))
+                (cond ((eq expanded form)
+                       (when compile-time-too
+                         (eval form))
+                       (convert-and-maybe-compile form path))
+                      (t
+                       (process-toplevel-form expanded
+                                              path
+                                              compile-time-too))))))))))
 
   (values))
 \f
 ;;;;
 ;;;; (See EMIT-MAKE-LOAD-FORM.)
 
-;;; Returns T iff we are currently producing a fasl-file and hence
+;;; Return T if we are currently producing a fasl file and hence
 ;;; constants need to be dumped carefully.
 (defun producing-fasl-file ()
-  (unless *converting-for-interpreter*
-    (fasl-file-p *compile-object*)))
+  (fasl-output-p *compile-object*))
 
 ;;; Compile FORM and arrange for it to be called at load-time. Return
 ;;; the dumper handle and our best guess at the type of the object.
     (values
      (fasl-dump-load-time-value-lambda lambda *compile-object*)
      (let ((type (leaf-type lambda)))
-       (if (function-type-p type)
-          (single-value-type (function-type-returns type))
+       (if (fun-type-p type)
+          (single-value-type (fun-type-returns type))
           *wild-type*)))))
 
 ;;; Compile the FORMS and arrange for them to be called (for effect,
 ;;; not value) at load time.
 (defun compile-make-load-form-init-forms (forms name)
   (let ((lambda (compile-load-time-stuff `(progn ,@forms) name nil)))
-    (fasl-dump-top-level-lambda-call lambda *compile-object*)))
+    (fasl-dump-toplevel-lambda-call lambda *compile-object*)))
 
 ;;; Does the actual work of COMPILE-LOAD-TIME-VALUE or
 ;;; COMPILE-MAKE-LOAD-FORM- INIT-FORMS.
 (defun compile-load-time-stuff (form name for-value)
   (with-ir1-namespace
    (let* ((*lexenv* (make-null-lexenv))
-         (lambda (ir1-top-level form *current-path* for-value)))
-     (setf (leaf-name lambda) name)
-     (compile-top-level (list lambda) t)
+         (lambda (ir1-toplevel form *current-path* for-value)))
+     (compile-toplevel (list lambda) t)
      lambda)))
 
-;;; Called by COMPILE-TOP-LEVEL when it was pased T for
+;;; This is called by COMPILE-TOPLEVEL when it was passed T for
 ;;; LOAD-TIME-VALUE-P (which happens in COMPILE-LOAD-TIME-STUFF). We
 ;;; don't try to combine this component with anything else and frob
-;;; the name. If not in a :TOP-LEVEL component, then don't bother
+;;; the name. If not in a :TOPLEVEL component, then don't bother
 ;;; compiling, because it was merged with a run-time component.
 (defun compile-load-time-value-lambda (lambdas)
-  (assert (null (cdr lambdas)))
+  (aver (null (cdr lambdas)))
   (let* ((lambda (car lambdas))
-        (component (block-component (node-block (lambda-bind lambda)))))
-    (when (eq (component-kind component) :top-level)
-      (setf (component-name component) (leaf-name lambda))
+        (component (lambda-component lambda)))
+    (when (eql (component-kind component) :toplevel)
+      (setf (component-name component) (leaf-debug-name lambda))
       (compile-component component)
       (clear-ir1-info component))))
-
-;;; The entry point for MAKE-LOAD-FORM support. When IR1 conversion
-;;; finds a constant structure, it invokes this to arrange for proper
-;;; dumping. If it turns out that the constant has already been
-;;; dumped, then we don't need to do anything.
-;;;
-;;; If the constant hasn't been dumped, then we check to see whether
-;;; we are in the process of creating it. We detect this by
-;;; maintaining the special *CONSTANTS-BEING-CREATED* as a list of all
-;;; the constants we are in the process of creating. Actually, each
-;;; entry is a list of the constant and any init forms that need to be
-;;; processed on behalf of that constant.
-;;;
-;;; It's not necessarily an error for this to happen. If we are
-;;; processing the init form for some object that showed up *after*
-;;; the original reference to this constant, then we just need to
-;;; defer the processing of that init form. To detect this, we
-;;; maintain *CONSTANTS-CREATED-SINCE-LAST-INIT* as a list of the
-;;; constants created since the last time we started processing an
-;;; init form. If the constant passed to emit-make-load-form shows up
-;;; in this list, then there is a circular chain through creation
-;;; forms, which is an error.
-;;;
-;;; If there is some intervening init form, then we blow out of
-;;; processing it by throwing to the tag PENDING-INIT. The value we
-;;; throw is the entry from *CONSTANTS-BEING-CREATED*. This is so the
-;;; offending init form can be tacked onto the init forms for the
-;;; circular object.
-;;;
-;;; If the constant doesn't show up in *CONSTANTS-BEING-CREATED*, then
-;;; we have to create it. We call MAKE-LOAD-FORM and check to see
-;;; whether the creation form is the magic value
-;;; :JUST-DUMP-IT-NORMALLY. If it is, then we don't do anything. The
-;;; dumper will eventually get its hands on the object and use the
-;;; normal structure dumping noise on it.
-;;;
-;;; Otherwise, we bind *CONSTANTS-BEING-CREATED* and
-;;; *CONSTANTS-CREATED-SINCE- LAST-INIT* and compile the creation form
-;;; much the way LOAD-TIME-VALUE does. When this finishes, we tell the
-;;; dumper to use that result instead whenever it sees this constant.
-;;;
-;;; Now we try to compile the init form. We bind
-;;; *CONSTANTS-CREATED-SINCE- LAST-INIT* to NIL and compile the init
-;;; form (and any init forms that were added because of circularity
-;;; detection). If this works, great. If not, we add the init forms to
-;;; the init forms for the object that caused the problems and let it
-;;; deal with it.
-(defvar *constants-being-created* nil)
-(defvar *constants-created-since-last-init* nil)
-;;; FIXME: Shouldn't these^ variables be bound in LET forms?
-(defun emit-make-load-form (constant)
-  (assert (fasl-file-p *compile-object*))
-  (unless (or (fasl-constant-already-dumped constant *compile-object*)
-             ;; KLUDGE: This special hack is because I was too lazy
-             ;; to rework DEF!STRUCT so that the MAKE-LOAD-FORM
-             ;; function of LAYOUT returns nontrivial forms when
-             ;; building the cross-compiler but :IGNORE-IT when
-             ;; cross-compiling or running under the target Lisp. --
-             ;; WHN 19990914
-             #+sb-xc-host (typep constant 'layout))
-    (let ((circular-ref (assoc constant *constants-being-created* :test #'eq)))
-      (when circular-ref
-       (when (find constant *constants-created-since-last-init* :test #'eq)
-         (throw constant t))
-       (throw 'pending-init circular-ref)))
-    (multiple-value-bind (creation-form init-form)
-       (handler-case
-           (sb!xc:make-load-form constant (make-null-lexenv))
-         (error (condition)
-                (compiler-error "(while making load form for ~S)~%~A"
-                                constant
-                                condition)))
-      (case creation-form
-       (:just-dump-it-normally
-        (fasl-validate-structure constant *compile-object*)
-        t)
-       (:ignore-it
-        nil)
-       (t
-        (compile-top-level-lambdas () t)
-        (when (fasl-constant-already-dumped constant *compile-object*)
-          (return-from emit-make-load-form nil))
-        (let* ((name (let ((*print-level* 1) (*print-length* 2))
-                       (with-output-to-string (stream)
-                         (write constant :stream stream))))
-               (info (if init-form
-                         (list constant name init-form)
-                         (list constant))))
-          (let ((*constants-being-created*
-                 (cons info *constants-being-created*))
-                (*constants-created-since-last-init*
-                 (cons constant *constants-created-since-last-init*)))
-            (when
-                (catch constant
-                  (fasl-note-handle-for-constant
-                   constant
-                   (compile-load-time-value
-                    creation-form
-                    (format nil "creation form for ~A" name))
-                   *compile-object*)
-                  nil)
-              (compiler-error "circular references in creation form for ~S"
-                              constant)))
-          (when (cdr info)
-            (let* ((*constants-created-since-last-init* nil)
-                   (circular-ref
-                    (catch 'pending-init
-                      (loop for (name form) on (cdr info) by #'cddr
-                        collect name into names
-                        collect form into forms
-                        finally
-                        (compile-make-load-form-init-forms
-                         forms
-                         (format nil "init form~:[~;s~] for ~{~A~^, ~}"
-                                 (cdr forms) names)))
-                      nil)))
-              (when circular-ref
-                (setf (cdr circular-ref)
-                      (append (cdr circular-ref) (cdr info))))))))))))
 \f
 ;;;; COMPILE-FILE
 
-;;; We build a list of top-level lambdas, and then periodically smash
+;;; We build a list of top level lambdas, and then periodically smash
 ;;; them together into a single component and compile it.
-(defvar *pending-top-level-lambdas*)
+(defvar *pending-toplevel-lambdas*)
 
-;;; The maximum number of top-level lambdas we put in a single
-;;; top-level component.
+;;; The maximum number of top level lambdas we put in a single
+;;; top level component.
 ;;;
 ;;; CMU CL 18b used this nontrivially by default (setting it to 10)
 ;;; but consequently suffered from the inability to execute some
 ;;; GENESIS, which is desirable, since at least for SBCL version
 ;;; 0.6.7, this is the high water mark for memory usage during system
 ;;; construction.
-(defparameter *top-level-lambda-max* 0)
+(defparameter *toplevel-lambda-max* 0)
 
-(defun object-call-top-level-lambda (tll)
+(defun object-call-toplevel-lambda (tll)
   (declare (type functional tll))
   (let ((object *compile-object*))
     (etypecase object
-      (fasl-file
-       (fasl-dump-top-level-lambda-call tll object))
+      (fasl-output
+       (fasl-dump-toplevel-lambda-call tll object))
       (core-object
-       (core-call-top-level-lambda tll object))
+       (core-call-toplevel-lambda tll object))
       (null))))
 
 ;;; Add LAMBDAS to the pending lambdas. If this leaves more than
-;;; *TOP-LEVEL-LAMBDA-MAX* lambdas in the list, or if FORCE-P is true,
+;;; *TOPLEVEL-LAMBDA-MAX* lambdas in the list, or if FORCE-P is true,
 ;;; then smash the lambdas into a single component, compile it, and
 ;;; call the resulting function.
-(defun sub-compile-top-level-lambdas (lambdas force-p)
+(defun sub-compile-toplevel-lambdas (lambdas force-p)
   (declare (list lambdas))
-  (setq *pending-top-level-lambdas*
-       (append *pending-top-level-lambdas* lambdas))
-  (let ((pending *pending-top-level-lambdas*))
+  (setq *pending-toplevel-lambdas*
+       (append *pending-toplevel-lambdas* lambdas))
+  (let ((pending *pending-toplevel-lambdas*))
     (when (and pending
-              (or (> (length pending) *top-level-lambda-max*)
+              (or (> (length pending) *toplevel-lambda-max*)
                   force-p))
-      (multiple-value-bind (component tll) (merge-top-level-lambdas pending)
-       (setq *pending-top-level-lambdas* ())
-       (let ((*byte-compile* (if (eq *byte-compile* :maybe)
-                                 *byte-compile-top-level*
-                                 *byte-compile*)))
-         (compile-component component))
+      (multiple-value-bind (component tll) (merge-toplevel-lambdas pending)
+       (setq *pending-toplevel-lambdas* ())
+       (compile-component component)
        (clear-ir1-info component)
-       (object-call-top-level-lambda tll))))
+       (object-call-toplevel-lambda tll))))
   (values))
 
-;;; Compile top-level code and call the top-level lambdas. We pick off
-;;; top-level lambdas in non-top-level components here, calling
-;;; SUB-c-t-l-l on each subsequence of normal top-level lambdas.
-(defun compile-top-level-lambdas (lambdas force-p)
+;;; Compile top level code and call the top level lambdas. We pick off
+;;; top level lambdas in non-top-level components here, calling
+;;; SUB-c-t-l-l on each subsequence of normal top level lambdas.
+(defun compile-toplevel-lambdas (lambdas force-p)
   (declare (list lambdas))
   (let ((len (length lambdas)))
     (flet ((loser (start)
-            (or (position-if #'(lambda (x)
-                                 (not (eq (component-kind
-                                           (block-component
-                                            (node-block
-                                             (lambda-bind x))))
-                                          :top-level)))
+            (or (position-if (lambda (x)
+                               (not (eq (component-kind
+                                         (block-component
+                                          (node-block
+                                           (lambda-bind x))))
+                                        :toplevel)))
                              lambdas
                              :start start)
                 len)))
            (loser (loser start) (loser start)))
           ((>= start len)
            (when force-p
-             (sub-compile-top-level-lambdas nil t)))
-       (sub-compile-top-level-lambdas (subseq lambdas start loser)
-                                      (or force-p (/= loser len)))
+             (sub-compile-toplevel-lambdas nil t)))
+       (sub-compile-toplevel-lambdas (subseq lambdas start loser)
+                                     (or force-p (/= loser len)))
        (unless (= loser len)
-         (object-call-top-level-lambda (elt lambdas loser))))))
+         (object-call-toplevel-lambda (elt lambdas loser))))))
   (values))
 
-;;; Compile LAMBDAS (a list of the lambdas for top-level forms) into
-;;; the object file. We loop doing local call analysis until it
-;;; converges, since a single pass might miss something due to
-;;; components being joined by LET conversion.
+;;; Compile LAMBDAS (a list of CLAMBDAs for top level forms) into the
+;;; object file. 
 ;;;
 ;;; LOAD-TIME-VALUE-P seems to control whether it's MAKE-LOAD-FORM and
 ;;; COMPILE-LOAD-TIME-VALUE stuff. -- WHN 20000201
-(defun compile-top-level (lambdas load-time-value-p)
+(defun compile-toplevel (lambdas load-time-value-p)
   (declare (list lambdas))
+
   (maybe-mumble "locall ")
-  (loop
-    (let ((did-something nil))
-      (dolist (lambda lambdas)
-       (let* ((component (block-component (node-block (lambda-bind lambda))))
-              (*all-components* (list component)))
-         (when (component-new-functions component)
-           (setq did-something t)
-           (local-call-analyze component))))
-      (unless did-something (return))))
+  (locall-analyze-clambdas-until-done lambdas)
 
   (maybe-mumble "IDFO ")
   (multiple-value-bind (components top-components hairy-top)
       (find-initial-dfo lambdas)
     (let ((*all-components* (append components top-components))
-         (top-level-closure nil))
+         (toplevel-closure nil))
       (when *check-consistency*
        (maybe-mumble "[check]~%")
        (check-ir1-consistency *all-components*))
 
       (dolist (component (append hairy-top top-components))
-       (when (pre-environment-analyze-top-level component)
-         (setq top-level-closure t)))
-
-      (let ((*byte-compile*
-            (if (and top-level-closure (eq *byte-compile* :maybe))
-                nil
-                *byte-compile*)))
-       (dolist (component components)
-         (compile-component component)
-         (when (replace-top-level-xeps component)
-           (setq top-level-closure t)))
+       (when (pre-physenv-analyze-toplevel component)
+         (setq toplevel-closure t)))
+
+      (dolist (component components)
+       (compile-component component)
+       (when (replace-toplevel-xeps component)
+         (setq toplevel-closure t)))
        
-       (when *check-consistency*
-         (maybe-mumble "[check]~%")
-         (check-ir1-consistency *all-components*))
+      (when *check-consistency*
+       (maybe-mumble "[check]~%")
+       (check-ir1-consistency *all-components*))
        
-       (if load-time-value-p
-           (compile-load-time-value-lambda lambdas)
-           (compile-top-level-lambdas lambdas top-level-closure)))
+      (if load-time-value-p
+         (compile-load-time-value-lambda lambdas)
+         (compile-toplevel-lambdas lambdas toplevel-closure))
 
-      (dolist (component components)
-       (clear-ir1-info component))
+      (mapc #'clear-ir1-info components)
       (clear-stuff)))
   (values))
 
 ;;; compilation.
 (defun finish-block-compilation ()
   (when *block-compile*
-    (when *top-level-lambdas*
-      (compile-top-level (nreverse *top-level-lambdas*) nil)
-      (setq *top-level-lambdas* ()))
+    (when *toplevel-lambdas*
+      (compile-toplevel (nreverse *toplevel-lambdas*) nil)
+      (setq *toplevel-lambdas* ()))
     (setq *block-compile* nil)
     (setq *entry-points* nil)))
 
 ;;; Read all forms from INFO and compile them, with output to OBJECT.
 ;;; Return (VALUES NIL WARNINGS-P FAILURE-P).
-(defun sub-compile-file (info &optional d-s-info)
+(defun sub-compile-file (info)
   (declare (type source-info info))
-  (let* (;; These are bound in WITH-COMPILATION-UNIT now. -- WHN 20000308
-        #+nil (*compiler-error-count* 0)
-        #+nil (*compiler-warning-count* 0)
-        #+nil (*compiler-style-warning-count* 0)
-        #+nil (*compiler-note-count* 0)
-        (*block-compile* *block-compile-argument*)
+  (let* ((*block-compile* *block-compile-argument*)
         (*package* (sane-package))
-        (*initial-package* (sane-package))
-        (*initial-cookie* *default-cookie*)
-        (*initial-interface-cookie* *default-interface-cookie*)
-        (*default-cookie* (copy-cookie *initial-cookie*))
-        (*default-interface-cookie*
-         (copy-cookie *initial-interface-cookie*))
+        (*policy* *policy*)
         (*lexenv* (make-null-lexenv))
-        (*converting-for-interpreter* nil)
         (*source-info* info)
         (sb!xc:*compile-file-pathname* nil)
         (sb!xc:*compile-file-truename* nil)
-        (*top-level-lambdas* ())
-        (*pending-top-level-lambdas* ())
+        (*toplevel-lambdas* ())
+        (*pending-toplevel-lambdas* ())
         (*compiler-error-bailout*
          (lambda ()
            (compiler-mumble "~2&; fatal error, aborting compilation~%")
         (*last-format-string* nil)
         (*last-format-args* nil)
         (*last-message-count* 0)
-        (*info-environment* (or *backend-info-environment*
-                                *info-environment*))
+        ;; FIXME: Do we need this rebinding here? It's a literal
+        ;; translation of the old CMU CL rebinding to
+        ;; (OR *BACKEND-INFO-ENVIRONMENT* *INFO-ENVIRONMENT*),
+        ;; and it's not obvious whether the rebinding to itself is
+        ;; needed that SBCL doesn't need *BACKEND-INFO-ENVIRONMENT*.
+        (*info-environment* *info-environment*)
         (*gensym-counter* 0))
-    (with-compilation-values
-      (sb!xc:with-compilation-unit ()
-        (clear-stuff)
-
-       (process-sources info)
-
-       (finish-block-compilation)
-       (compile-top-level-lambdas () t)
-       (let ((object *compile-object*))
-         (etypecase object
-           (fasl-file (fasl-dump-source-info info object))
-           (core-object (fix-core-source-info info object d-s-info))
-           (null)))
-       nil))))
-
-;;; Return a list of pathnames for the named files. All the files must
-;;; exist.
-(defun verify-source-files (stuff)
-  (let* ((stuff (if (listp stuff) stuff (list stuff)))
-        (default-host (make-pathname
-                       :host (pathname-host (pathname (first stuff))))))
+    (handler-case
+       (with-compilation-values
+        (sb!xc:with-compilation-unit ()
+          (clear-stuff)
+
+          (sub-sub-compile-file info)
+
+          (finish-block-compilation)
+          (compile-toplevel-lambdas () t)
+          (let ((object *compile-object*))
+            (etypecase object
+              (fasl-output (fasl-dump-source-info info object))
+              (core-object (fix-core-source-info info object))
+              (null)))
+          nil))
+      ;; Some errors are sufficiently bewildering that we just fail
+      ;; immediately, without trying to recover and compile more of
+      ;; the input file.
+      (input-error-in-compile-file (condition)
+       (format *error-output*
+              "~@<compilation aborted because of input error: ~2I~_~A~:>"
+              condition)
+       (values nil t t)))))
+
+;;; Return a pathname for the named file. The file must exist.
+(defun verify-source-file (pathname-designator)
+  (let* ((pathname (pathname pathname-designator))
+        (default-host (make-pathname :host (pathname-host pathname))))
     (flet ((try-with-type (path type error-p)
             (let ((new (merge-pathnames
                         path (make-pathname :type type
               (if (probe-file new)
                   new
                   (and error-p (truename new))))))
-      (unless stuff
-       (error "can't compile with no source files"))
-      (mapcar #'(lambda (x)
-                 (let ((x (pathname x)))
-                   (cond ((typep x 'logical-pathname)
-                          (try-with-type x "LISP" t))
-                         ((probe-file x) x)
-                         ((try-with-type x "lisp"  nil))
-                         ((try-with-type x "lisp"  t)))))
-             stuff))))
+      (cond ((typep pathname 'logical-pathname)
+            (try-with-type pathname "LISP" t))
+           ((probe-file pathname) pathname)
+           ((try-with-type pathname "lisp"  nil))
+           ((try-with-type pathname "lisp"  t))))))
 
 (defun elapsed-time-to-string (tsec)
   (multiple-value-bind (tmin sec) (truncate tsec 60)
 ;;; Print some junk at the beginning and end of compilation.
 (defun start-error-output (source-info)
   (declare (type source-info source-info))
-  (dolist (x (source-info-files source-info))
+  (let ((file-info (source-info-file-info source-info)))
     (compiler-mumble "~&; compiling file ~S (written ~A):~%"
-                    (namestring (file-info-name x))
+                    (namestring (file-info-name file-info))
                     (sb!int:format-universal-time nil
-                                                  (file-info-write-date x)
+                                                  (file-info-write-date
+                                                   file-info)
                                                   :style :government
                                                   :print-weekday nil
                                                   :print-timezone nil)))
   (values))
-
 (defun finish-error-output (source-info won)
   (declare (type source-info source-info))
   (compiler-mumble "~&; compilation ~:[aborted after~;finished in~] ~A~&"
 
 ;;; Open some files and call SUB-COMPILE-FILE. If something unwinds
 ;;; out of the compile, then abort the writing of the output file, so
-;;; we don't overwrite it with known garbage.
+;;; that we don't overwrite it with known garbage.
 (defun sb!xc:compile-file
-    (source
+    (input-file
      &key
-     (output-file t) ; FIXME: ANSI says this should be a pathname designator.
+
+     ;; ANSI options
+     (output-file (cfp-output-file-default input-file))
      ;; FIXME: ANSI doesn't seem to say anything about
      ;; *COMPILE-VERBOSE* and *COMPILE-PRINT* being rebound by this
      ;; function..
      ((:verbose sb!xc:*compile-verbose*) sb!xc:*compile-verbose*)
      ((:print sb!xc:*compile-print*) sb!xc:*compile-print*)
      (external-format :default)
-     ((:block-compile *block-compile-argument*) nil)
-     ((:entry-points *entry-points*) nil)
-     ((:byte-compile *byte-compile*) *byte-compile-default*))
+
+     ;; extensions
+     (trace-file nil) 
+     ((:block-compile *block-compile-argument*) nil))
+
   #!+sb-doc
-  "Compile SOURCE, producing a corresponding FASL file. 
-   :Output-File
-      The name of the fasl to output, NIL for none, T for the default.
-   :Block-Compile
-      Determines whether multiple functions are compiled together as a unit,
-      resolving function references at compile time. NIL means that global
-      function names are never resolved at compilation time.
-   :Entry-Points
-      This specifies a list of function names for functions in the file(s) that
-      must be given global definitions. This only applies to block
-      compilation. If the value is NIL (the default) then all functions
-      will be globally defined.
-   :Byte-Compile {T | NIL | :MAYBE}
-      Determines whether to compile into interpreted byte code instead of
-      machine instructions. Byte code is several times smaller, but much
-      slower. If :MAYBE, then only byte-compile when SPEED is 0 and
-      DEBUG <= 1. The default is the value of SB-EXT:*BYTE-COMPILE-DEFAULT*,
-      which is initially :MAYBE."
+  "Compile INPUT-FILE, producing a corresponding fasl file and returning
+   its filename. Besides the ANSI &KEY arguments :OUTPUT-FILE, :VERBOSE,
+   :PRINT, and :EXTERNAL-FORMAT,the following extensions are supported:
+     :TRACE-FILE
+        If given, internal data structures are dumped to the specified
+        file, or if a value of T is given, to a file of *.trace type
+        derived from the input file name.
+   Also, as a workaround for vaguely-non-ANSI behavior, the :BLOCK-COMPILE
+   argument is quasi-supported, to determine whether multiple
+   functions are compiled together as a unit, resolving function
+   references at compile time. NIL means that global function names
+   are never resolved at compilation time. Currently NIL is the
+   default behavior, because although section 3.2.2.3, \"Semantic
+   Constraints\", of the ANSI spec allows this behavior under all
+   circumstances, the compiler's runtime scales badly when it
+   tries to do this for large files. If/when this performance
+   problem is fixed, the block compilation default behavior will
+   probably be made dependent on the SPEED and COMPILATION-SPEED
+   optimization values, and the :BLOCK-COMPILE argument will probably
+   become deprecated."
+
   (unless (eq external-format :default)
     (error "Non-:DEFAULT EXTERNAL-FORMAT values are not supported."))
-  (let* ((fasl-file nil)
+  (let* ((fasl-output nil)
         (output-file-name nil)
         (compile-won nil)
         (warnings-p nil)
         (failure-p t) ; T in case error keeps this from being set later
-
-        ;; KLUDGE: The listifying and unlistifying in the next calls
-        ;; is to interface to old CMU CL code which accepted and
-        ;; returned lists of multiple source files. It would be
-        ;; cleaner to redo VERIFY-SOURCE-FILES and as
-        ;; VERIFY-SOURCE-FILE, accepting a single source file, and
-        ;; do a similar transformation on MAKE-FILE-SOURCE-INFO too.
-        ;; -- WHN 20000201
-        (source (first (verify-source-files (list source))))
-        (source-info (make-file-source-info (list source))))
+        (input-pathname (verify-source-file input-file))
+        (source-info (make-file-source-info input-pathname))
+        (*compiler-trace-output* nil)) ; might be modified below
+                               
     (unwind-protect
        (progn
          (when output-file
            (setq output-file-name
-                 (sb!xc:compile-file-pathname source
-                                              :output-file output-file
-                                              :byte-compile *byte-compile*))
-           (setq fasl-file
-                 (open-fasl-file output-file-name
-                                 (namestring source)
-                                 (eq *byte-compile* t))))
+                 (sb!xc:compile-file-pathname input-file
+                                              :output-file output-file))
+           (setq fasl-output
+                 (open-fasl-output output-file-name
+                                   (namestring input-pathname))))
+         (when trace-file
+           (let* ((default-trace-file-pathname
+                    (make-pathname :type "trace" :defaults input-pathname))
+                  (trace-file-pathname
+                   (if (eql trace-file t)
+                       default-trace-file-pathname
+                       (merge-pathnames trace-file
+                                        default-trace-file-pathname))))
+             (setf *compiler-trace-output*
+                   (open trace-file-pathname
+                         :if-exists :supersede
+                         :direction :output))))
 
          (when sb!xc:*compile-verbose*
            (start-error-output source-info))
-         (let ((*compile-object* fasl-file)
+         (let ((*compile-object* fasl-output)
                dummy)
            (multiple-value-setq (dummy warnings-p failure-p)
              (sub-compile-file source-info)))
 
       (close-source-info source-info)
 
-      (when fasl-file
-       (close-fasl-file fasl-file (not compile-won))
-       (setq output-file-name (pathname (fasl-file-stream fasl-file)))
+      (when fasl-output
+       (close-fasl-output fasl-output (not compile-won))
+       (setq output-file-name
+             (pathname (fasl-output-stream fasl-output)))
        (when (and compile-won sb!xc:*compile-verbose*)
          (compiler-mumble "~2&; ~A written~%" (namestring output-file-name))))
 
       (when sb!xc:*compile-verbose*
-       (finish-error-output source-info compile-won)))
+       (finish-error-output source-info compile-won))
+
+      (when *compiler-trace-output*
+       (close *compiler-trace-output*)))
 
     (values (if output-file
                ;; Hack around filesystem race condition...
            warnings-p
            failure-p)))
 \f
-(defun sb!xc:compile-file-pathname (file-path
-                                   &key (output-file t) byte-compile
+;;; a helper function for COMPILE-FILE-PATHNAME: the default for
+;;; the OUTPUT-FILE argument
+;;;
+;;; ANSI: The defaults for the OUTPUT-FILE are taken from the pathname
+;;; that results from merging the INPUT-FILE with the value of
+;;; *DEFAULT-PATHNAME-DEFAULTS*, except that the type component should
+;;; default to the appropriate implementation-defined default type for
+;;; compiled files.
+(defun cfp-output-file-default (input-file)
+  (let* ((defaults (merge-pathnames input-file *default-pathname-defaults*))
+        (retyped (make-pathname :type *fasl-file-type* :defaults defaults)))
+    retyped))
+       
+;;; KLUDGE: Part of the ANSI spec for this seems contradictory:
+;;;   If INPUT-FILE is a logical pathname and OUTPUT-FILE is unsupplied,
+;;;   the result is a logical pathname. If INPUT-FILE is a logical
+;;;   pathname, it is translated into a physical pathname as if by
+;;;   calling TRANSLATE-LOGICAL-PATHNAME.
+;;; So I haven't really tried to make this precisely ANSI-compatible
+;;; at the level of e.g. whether it returns logical pathname or a
+;;; physical pathname. Patches to make it more correct are welcome.
+;;; -- WHN 2000-12-09
+(defun sb!xc:compile-file-pathname (input-file
+                                   &key
+                                   (output-file (cfp-output-file-default
+                                                 input-file))
                                    &allow-other-keys)
   #!+sb-doc
   "Return a pathname describing what file COMPILE-FILE would write to given
    these arguments."
-  (declare (values (or null pathname)))
-  (let ((pathname (pathname file-path)))
-    (cond ((not (eq output-file t))
-          (when output-file
-            (translate-logical-pathname (pathname output-file))))
-         ((and (typep pathname 'logical-pathname) (not (eq byte-compile t)))
-          (make-pathname :type "FASL" :defaults pathname
-                         :case :common))
-         (t
-          (make-pathname :defaults (translate-logical-pathname pathname)
-                         :type (if (eq byte-compile t)
-                                   (backend-byte-fasl-file-type)
-                                   *backend-fasl-file-type*))))))
+  (pathname output-file))
+\f
+;;;; MAKE-LOAD-FORM stuff
+
+;;; The entry point for MAKE-LOAD-FORM support. When IR1 conversion
+;;; finds a constant structure, it invokes this to arrange for proper
+;;; dumping. If it turns out that the constant has already been
+;;; dumped, then we don't need to do anything.
+;;;
+;;; If the constant hasn't been dumped, then we check to see whether
+;;; we are in the process of creating it. We detect this by
+;;; maintaining the special *CONSTANTS-BEING-CREATED* as a list of all
+;;; the constants we are in the process of creating. Actually, each
+;;; entry is a list of the constant and any init forms that need to be
+;;; processed on behalf of that constant.
+;;;
+;;; It's not necessarily an error for this to happen. If we are
+;;; processing the init form for some object that showed up *after*
+;;; the original reference to this constant, then we just need to
+;;; defer the processing of that init form. To detect this, we
+;;; maintain *CONSTANTS-CREATED-SINCE-LAST-INIT* as a list of the
+;;; constants created since the last time we started processing an
+;;; init form. If the constant passed to emit-make-load-form shows up
+;;; in this list, then there is a circular chain through creation
+;;; forms, which is an error.
+;;;
+;;; If there is some intervening init form, then we blow out of
+;;; processing it by throwing to the tag PENDING-INIT. The value we
+;;; throw is the entry from *CONSTANTS-BEING-CREATED*. This is so the
+;;; offending init form can be tacked onto the init forms for the
+;;; circular object.
+;;;
+;;; If the constant doesn't show up in *CONSTANTS-BEING-CREATED*, then
+;;; we have to create it. We call MAKE-LOAD-FORM and check to see
+;;; whether the creation form is the magic value
+;;; :JUST-DUMP-IT-NORMALLY. If it is, then we don't do anything. The
+;;; dumper will eventually get its hands on the object and use the
+;;; normal structure dumping noise on it.
+;;;
+;;; Otherwise, we bind *CONSTANTS-BEING-CREATED* and
+;;; *CONSTANTS-CREATED-SINCE- LAST-INIT* and compile the creation form
+;;; much the way LOAD-TIME-VALUE does. When this finishes, we tell the
+;;; dumper to use that result instead whenever it sees this constant.
+;;;
+;;; Now we try to compile the init form. We bind
+;;; *CONSTANTS-CREATED-SINCE-LAST-INIT* to NIL and compile the init
+;;; form (and any init forms that were added because of circularity
+;;; detection). If this works, great. If not, we add the init forms to
+;;; the init forms for the object that caused the problems and let it
+;;; deal with it.
+(defvar *constants-being-created* nil)
+(defvar *constants-created-since-last-init* nil)
+;;; FIXME: Shouldn't these^ variables be bound in LET forms?
+(defun emit-make-load-form (constant)
+  (aver (fasl-output-p *compile-object*))
+  (unless (or (fasl-constant-already-dumped-p constant *compile-object*)
+             ;; KLUDGE: This special hack is because I was too lazy
+             ;; to rework DEF!STRUCT so that the MAKE-LOAD-FORM
+             ;; function of LAYOUT returns nontrivial forms when
+             ;; building the cross-compiler but :IGNORE-IT when
+             ;; cross-compiling or running under the target Lisp. --
+             ;; WHN 19990914
+             #+sb-xc-host (typep constant 'layout))
+    (let ((circular-ref (assoc constant *constants-being-created* :test #'eq)))
+      (when circular-ref
+       (when (find constant *constants-created-since-last-init* :test #'eq)
+         (throw constant t))
+       (throw 'pending-init circular-ref)))
+    (multiple-value-bind (creation-form init-form)
+       (handler-case
+           (sb!xc:make-load-form constant (make-null-lexenv))
+         (error (condition)
+                (compiler-error "(while making load form for ~S)~%~A"
+                                constant
+                                condition)))
+      (case creation-form
+       (:just-dump-it-normally
+        (fasl-validate-structure constant *compile-object*)
+        t)
+       (:ignore-it
+        nil)
+       (t
+        (compile-toplevel-lambdas () t)
+        (when (fasl-constant-already-dumped-p constant *compile-object*)
+          (return-from emit-make-load-form nil))
+        (let* ((name (let ((*print-level* 1) (*print-length* 2))
+                       (with-output-to-string (stream)
+                         (write constant :stream stream))))
+               (info (if init-form
+                         (list constant name init-form)
+                         (list constant))))
+          (let ((*constants-being-created*
+                 (cons info *constants-being-created*))
+                (*constants-created-since-last-init*
+                 (cons constant *constants-created-since-last-init*)))
+            (when
+                (catch constant
+                  (fasl-note-handle-for-constant
+                   constant
+                   (compile-load-time-value
+                    creation-form
+                    (format nil "creation form for ~A" name))
+                   *compile-object*)
+                  nil)
+              (compiler-error "circular references in creation form for ~S"
+                              constant)))
+          (when (cdr info)
+            (let* ((*constants-created-since-last-init* nil)
+                   (circular-ref
+                    (catch 'pending-init
+                      (loop for (name form) on (cdr info) by #'cddr
+                        collect name into names
+                        collect form into forms
+                        finally
+                        (compile-make-load-form-init-forms
+                         forms
+                         (format nil "init form~:[~;s~] for ~{~A~^, ~}"
+                                 (cdr forms) names)))
+                      nil)))
+              (when circular-ref
+                (setf (cdr circular-ref)
+                      (append (cdr circular-ref) (cdr info))))))))))))