0.6.8.16:
[sbcl.git] / src / compiler / main.lisp
1 ;;;; the top-level interfaces to the compiler
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; This software is derived from the CMU CL system, which was
7 ;;;; written at Carnegie Mellon University and released into the
8 ;;;; public domain. The software is in the public domain and is
9 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
10 ;;;; files for more information.
11
12 (in-package "SB!C")
13
14 ;;; FIXME: Doesn't this belong somewhere else, like early-c.lisp?
15 (declaim (special *constants* *free-variables* *component-being-compiled*
16                   *code-vector* *next-location* *result-fixups*
17                   *free-functions* *source-paths*
18                   *seen-blocks* *seen-functions* *list-conflicts-table*
19                   *continuation-number* *continuation-numbers*
20                   *number-continuations* *tn-id* *tn-ids* *id-tns*
21                   *label-ids* *label-id* *id-labels*
22                   *undefined-warnings* *compiler-error-count*
23                   *compiler-warning-count* *compiler-style-warning-count*
24                   *compiler-note-count*
25                   *compiler-error-bailout*
26                   #!+sb-show *compiler-trace-output*
27                   *last-source-context* *last-original-source*
28                   *last-source-form* *last-format-string* *last-format-args*
29                   *last-message-count* *lexenv*))
30
31 (defvar *byte-compile-default* :maybe
32   #!+sb-doc
33   "the default value for the :BYTE-COMPILE argument to COMPILE-FILE")
34
35 (defvar *byte-compile-top-level*
36   #-sb-xc-host t
37   #+sb-xc-host nil ; since the byte compiler isn't supported in cross-compiler
38   #!+sb-doc
39   "Similar to *BYTE-COMPILE-DEFAULT*, but controls the compilation of top-level
40    forms (evaluated at load-time) when the :BYTE-COMPILE argument is :MAYBE
41    (the default.)  When true, we decide to byte-compile.")
42
43 ;;; default value of the :BYTE-COMPILE argument to the compiler
44 (defvar *byte-compile* :maybe)
45
46 ;;; Bound by COMPILE-COMPONENT to T when byte-compiling, and NIL when
47 ;;; native compiling. During IR1 conversion this can also be :MAYBE,
48 ;;; in which case we must look at the policy, see (byte-compiling).
49 (defvar *byte-compiling* :maybe)
50 (declaim (type (member t nil :maybe) *byte-compile* *byte-compiling*
51                *byte-compile-default*))
52
53 (defvar *check-consistency* nil)
54 (defvar *all-components*)
55
56 ;;; Bind this to a stream to capture various internal debugging output.
57 #!+sb-show
58 (defvar *compiler-trace-output* nil)
59
60 ;;; The current block compilation state. These are initialized to the
61 ;;; :BLOCK-COMPILE and :ENTRY-POINTS arguments that COMPILE-FILE was
62 ;;; called with.
63 ;;;
64 ;;; *BLOCK-COMPILE-ARGUMENT* holds the original value of the
65 ;;; :BLOCK-COMPILE argument, which overrides any internal
66 ;;; declarations.
67 (defvar *block-compile*)
68 (defvar *block-compile-argument*)
69 (declaim (type (member nil t :specified)
70                *block-compile* *block-compile-argument*))
71 (defvar *entry-points*)
72 (declaim (list *entry-points*))
73
74 ;;; When block compiling, used by PROCESS-FORM to accumulate top-level
75 ;;; lambdas resulting from compiling subforms. (In reverse order.)
76 (defvar *top-level-lambdas*)
77 (declaim (list *top-level-lambdas*))
78
79 (defvar sb!xc:*compile-verbose* t
80   #!+sb-doc
81   "The default for the :VERBOSE argument to COMPILE-FILE.")
82 (defvar sb!xc:*compile-print* t
83   #!+sb-doc
84   "The default for the :PRINT argument to COMPILE-FILE.")
85 (defvar *compile-progress* nil
86   #!+sb-doc
87   "When this is true, the compiler prints to *ERROR-OUTPUT* progress
88   information about the phases of compilation of each function. (This
89   is useful mainly in large block compilations.)")
90
91 (defvar sb!xc:*compile-file-pathname* nil
92   #!+sb-doc
93   "The defaulted pathname of the file currently being compiled, or NIL if not
94   compiling.")
95 (defvar sb!xc:*compile-file-truename* nil
96   #!+sb-doc
97   "The TRUENAME of the file currently being compiled, or NIL if not
98   compiling.")
99
100 (declaim (type (or pathname null)
101                sb!xc:*compile-file-pathname*
102                sb!xc:*compile-file-truename*))
103
104 ;;; the values of *PACKAGE* and policy when compilation started
105 (defvar *initial-package*)
106 (defvar *initial-cookie*)
107 (defvar *initial-interface-cookie*)
108
109 ;;; The source-info structure for the current compilation. This is null
110 ;;; globally to indicate that we aren't currently in any identifiable
111 ;;; compilation.
112 (defvar *source-info* nil)
113
114 ;;; True if we are within a WITH-COMPILATION-UNIT form (which normally
115 ;;; causes nested uses to be no-ops).
116 (defvar *in-compilation-unit* nil)
117
118 ;;; Count of the number of compilation units dynamically enclosed by
119 ;;; the current active WITH-COMPILATION-UNIT that were unwound out of.
120 (defvar *aborted-compilation-unit-count*)
121
122 ;;; Mumble conditional on *COMPILE-PROGRESS*.
123 (defun maybe-mumble (&rest foo)
124   (when *compile-progress*
125     ;; MNA: compiler message patch
126     (compiler-mumble "~&")
127     (pprint-logical-block (*error-output* nil :per-line-prefix "; ")
128        (apply #'compiler-mumble foo))))
129
130 (deftype object () '(or fasl-file core-object null))
131
132 (defvar *compile-object* nil)
133 (declaim (type object *compile-object*))
134 \f
135 ;;;; WITH-COMPILATION-UNIT and WITH-COMPILATION-VALUES
136
137 (defmacro sb!xc:with-compilation-unit (options &body body)
138   #!+sb-doc
139   "WITH-COMPILATION-UNIT ({Key Value}*) Form*
140   This form affects compilations that take place within its dynamic extent. It
141   is intended to be wrapped around the compilation of all files in the same
142   system. These keywords are defined:
143     :OVERRIDE Boolean-Form
144         One of the effects of this form is to delay undefined warnings
145         until the end of the form, instead of giving them at the end of each
146         compilation. If OVERRIDE is NIL (the default), then the outermost
147         WITH-COMPILATION-UNIT form grabs the undefined warnings. Specifying
148         OVERRIDE true causes that form to grab any enclosed warnings, even if
149         it is enclosed by another WITH-COMPILATION-UNIT."
150   `(%with-compilation-unit (lambda () ,@body) ,@options))
151
152 (defun %with-compilation-unit (fn &key override)
153   (let ((succeeded-p nil))
154     (if (and *in-compilation-unit* (not override))
155         ;; Inside another WITH-COMPILATION-UNIT, a WITH-COMPILATION-UNIT is
156         ;; ordinarily (unless OVERRIDE) basically a no-op.
157         (unwind-protect
158             (multiple-value-prog1 (funcall fn) (setf succeeded-p t))
159           (unless succeeded-p
160             (incf *aborted-compilation-unit-count*)))
161         ;; FIXME: Now *COMPILER-FOO-COUNT* stuff is bound in more than
162         ;; one place. If we can get rid of the IR1 interpreter, this
163         ;; should be easier to clean up.
164         (let ((*aborted-compilation-unit-count* 0)
165               (*compiler-error-count* 0)
166               (*compiler-warning-count* 0)
167               (*compiler-style-warning-count* 0)
168               (*compiler-note-count* 0)
169               (*undefined-warnings* nil)
170               (*in-compilation-unit* t))
171           (handler-bind ((parse-unknown-type
172                           (lambda (c)
173                             (note-undefined-reference
174                              (parse-unknown-type-specifier c)
175                              :type))))
176             (unwind-protect
177                 (multiple-value-prog1 (funcall fn) (setf succeeded-p t))
178               (unless succeeded-p
179                 (incf *aborted-compilation-unit-count*))
180               (summarize-compilation-unit (not succeeded-p))))))))
181
182 ;;; This is to be called at the end of a compilation unit. It signals
183 ;;; any residual warnings about unknown stuff, then prints the total
184 ;;; error counts. ABORT-P should be true when the compilation unit was
185 ;;; aborted by throwing out. ABORT-COUNT is the number of dynamically
186 ;;; enclosed nested compilation units that were aborted.
187 (defun summarize-compilation-unit (abort-p)
188   (unless abort-p
189     (handler-bind ((style-warning #'compiler-style-warning-handler)
190                    (warning #'compiler-warning-handler))
191
192       (let ((undefs (sort *undefined-warnings* #'string<
193                           :key #'(lambda (x)
194                                    (let ((x (undefined-warning-name x)))
195                                      (if (symbolp x)
196                                          (symbol-name x)
197                                          (prin1-to-string x)))))))
198         (unless *converting-for-interpreter*
199           (dolist (undef undefs)
200             (let ((name (undefined-warning-name undef))
201                   (kind (undefined-warning-kind undef))
202                   (warnings (undefined-warning-warnings undef))
203                   (undefined-warning-count (undefined-warning-count undef)))
204               (dolist (*compiler-error-context* warnings)
205                 (compiler-style-warning "undefined ~(~A~): ~S" kind name))
206
207               (let ((warn-count (length warnings)))
208                 (when (and warnings (> undefined-warning-count warn-count))
209                   (let ((more (- undefined-warning-count warn-count)))
210                     (compiler-style-warning
211                      "~D more use~:P of undefined ~(~A~) ~S"
212                      more kind name)))))))
213         
214         (dolist (kind '(:variable :function :type))
215           (let ((summary (mapcar #'undefined-warning-name
216                                  (remove kind undefs :test-not #'eq
217                                          :key #'undefined-warning-kind))))
218             (when summary
219               (compiler-style-warning
220                "~:[This ~(~A~) is~;These ~(~A~)s are~] undefined:~
221                 ~%  ~{~<~%  ~1:;~S~>~^ ~}"
222                (cdr summary) kind summary)))))))
223
224   (unless (or *converting-for-interpreter*
225               (and (not abort-p)
226                    (zerop *aborted-compilation-unit-count*)
227                    (zerop *compiler-error-count*)
228                    (zerop *compiler-warning-count*)
229                    (zerop *compiler-style-warning-count*)
230                    (zerop *compiler-note-count*)))
231     ;; MNA: compiler message patch
232     (format *error-output* "~&")
233     (pprint-logical-block (*error-output* nil :per-line-prefix "; ")
234     (compiler-mumble
235                            "compilation unit ~:[finished~;aborted~]~
236       ~[~:;~:*~&  caught ~D fatal ERROR condition~:P~]~
237       ~[~:;~:*~&  caught ~D ERROR condition~:P~]~
238       ~[~:;~:*~&  caught ~D WARNING condition~:P~]~
239       ~[~:;~:*~&  caught ~D STYLE-WARNING condition~:P~]~
240       ~[~:;~:*~&  printed ~D note~:P~]"
241      abort-p
242      *aborted-compilation-unit-count*
243      *compiler-error-count*
244      *compiler-warning-count*
245      *compiler-style-warning-count*
246                            *compiler-note-count*))))
247
248 ;;; Evaluate BODY, then return (VALUES BODY-VALUE WARNINGS-P
249 ;;; FAILURE-P), where BODY-VALUE is the first value of the body, and
250 ;;; WARNINGS-P and FAILURE-P are as in CL:COMPILE or CL:COMPILE-FILE.
251 ;;; This also wraps up WITH-IR1-NAMESPACE functionality.
252 (defmacro with-compilation-values (&body body)
253   `(with-ir1-namespace
254     (let ((*warnings-p* nil)
255           (*failure-p* nil))
256       (values (progn ,@body)
257               *warnings-p*
258               *failure-p*))))
259 \f
260 ;;;; component compilation
261
262 (defparameter *max-optimize-iterations* 3 ; ARB
263   #!+sb-doc
264   "The upper limit on the number of times that we will consecutively do IR1
265   optimization that doesn't introduce any new code. A finite limit is
266   necessary, since type inference may take arbitrarily long to converge.")
267
268 (defevent ir1-optimize-until-done "IR1-OPTIMIZE-UNTIL-DONE called")
269 (defevent ir1-optimize-maxed-out "hit *MAX-OPTIMIZE-ITERATIONS* limit")
270
271 ;;; Repeatedly optimize COMPONENT until no further optimizations can
272 ;;; be found or we hit our iteration limit. When we hit the limit, we
273 ;;; clear the component and block REOPTIMIZE flags to discourage the
274 ;;; next optimization attempt from pounding on the same code.
275 (defun ir1-optimize-until-done (component)
276   (declare (type component component))
277   (maybe-mumble "opt")
278   (event ir1-optimize-until-done)
279   (let ((count 0)
280         (cleared-reanalyze nil))
281     (loop
282       (when (component-reanalyze component)
283         (setq count 0)
284         (setq cleared-reanalyze t)
285         (setf (component-reanalyze component) nil))
286       (setf (component-reoptimize component) nil)
287       (ir1-optimize component)
288       (unless (component-reoptimize component)
289         (maybe-mumble " ")
290         (return))
291       (incf count)
292       (when (= count *max-optimize-iterations*)
293         (event ir1-optimize-maxed-out)
294         (maybe-mumble "* ")
295         (setf (component-reoptimize component) nil)
296         (do-blocks (block component)
297           (setf (block-reoptimize block) nil))
298         (return))
299       (maybe-mumble "."))
300     (when cleared-reanalyze
301       (setf (component-reanalyze component) t)))
302   (values))
303
304 (defparameter *constraint-propagate* t)
305 (defparameter *reoptimize-after-type-check-max* 5)
306
307 (defevent reoptimize-maxed-out
308   "*REOPTIMIZE-AFTER-TYPE-CHECK-MAX* exceeded.")
309
310 ;;; Iterate doing FIND-DFO until no new dead code is discovered.
311 (defun dfo-as-needed (component)
312   (declare (type component component))
313   (when (component-reanalyze component)
314     (maybe-mumble "DFO")
315     (loop
316       (find-dfo component)
317       (unless (component-reanalyze component)
318         (maybe-mumble " ")
319         (return))
320       (maybe-mumble ".")))
321   (values))
322
323 ;;; Do all the IR1 phases for a non-top-level component.
324 (defun ir1-phases (component)
325   (declare (type component component))
326   (let ((*constraint-number* 0)
327         (loop-count 1))
328     (declare (special *constraint-number*))
329     (loop
330       (ir1-optimize-until-done component)
331       (when (or (component-new-functions component)
332                 (component-reanalyze-functions component))
333         (maybe-mumble "locall ")
334         (local-call-analyze component))
335       (dfo-as-needed component)
336       (when *constraint-propagate*
337         (maybe-mumble "constraint ")
338         (constraint-propagate component))
339       (maybe-mumble "type ")
340       ;; Delay the generation of type checks until the type
341       ;; constraints have had time to propagate, else the compiler can
342       ;; confuse itself.
343       (unless (and (or (component-reoptimize component)
344                        (component-reanalyze component)
345                        (component-new-functions component)
346                        (component-reanalyze-functions component))
347                    (< loop-count (- *reoptimize-after-type-check-max* 2)))
348         (generate-type-checks component)
349         (unless (or (component-reoptimize component)
350                     (component-reanalyze component)
351                     (component-new-functions component)
352                     (component-reanalyze-functions component))
353           (return)))
354       (when (>= loop-count *reoptimize-after-type-check-max*)
355         (maybe-mumble "[reoptimize limit]")
356         (event reoptimize-maxed-out)
357         (return))
358       (incf loop-count)))
359
360   (ir1-finalize component)
361   (values))
362
363 (defun native-compile-component (component)
364   (let ((*code-segment* nil)
365         (*elsewhere* nil))
366     (maybe-mumble "GTN ")
367     (gtn-analyze component)
368     (maybe-mumble "LTN ")
369     (ltn-analyze component)
370     (dfo-as-needed component)
371     (maybe-mumble "control ")
372     (control-analyze component #'make-ir2-block)
373
374     (when (ir2-component-values-receivers (component-info component))
375       (maybe-mumble "stack ")
376       (stack-analyze component)
377       ;; Assign BLOCK-NUMBER for any cleanup blocks introduced by
378       ;; stack analysis. There shouldn't be any unreachable code after
379       ;; control, so this won't delete anything.
380       (dfo-as-needed component))
381
382     (unwind-protect
383         (progn
384           (maybe-mumble "IR2tran ")
385           (init-assembler)
386           (entry-analyze component)
387           (ir2-convert component)
388
389           (when (policy nil (>= speed cspeed))
390             (maybe-mumble "copy ")
391             (copy-propagate component))
392
393           (select-representations component)
394
395           (when *check-consistency*
396             (maybe-mumble "check2 ")
397             (check-ir2-consistency component))
398
399           (delete-unreferenced-tns component)
400
401           (maybe-mumble "life ")
402           (lifetime-analyze component)
403
404           (when *compile-progress*
405             (compiler-mumble "") ; Sync before doing more output.
406             (pre-pack-tn-stats component *error-output*))
407
408           (when *check-consistency*
409             (maybe-mumble "check-life ")
410             (check-life-consistency component))
411
412           (maybe-mumble "pack ")
413           (pack component)
414
415           (when *check-consistency*
416             (maybe-mumble "check-pack ")
417             (check-pack-consistency component))
418
419           #!+sb-show
420           (when *compiler-trace-output*
421             (describe-component component *compiler-trace-output*)
422             (describe-ir2-component component *compiler-trace-output*))
423
424           (maybe-mumble "code ")
425           (multiple-value-bind (code-length trace-table fixups)
426               (generate-code component)
427
428             #!+sb-show
429             (when *compiler-trace-output*
430               (format *compiler-trace-output*
431                       "~|~%disassembly of code for ~S~2%" component)
432               (sb!disassem:disassemble-assem-segment *code-segment*
433                                                      *compiler-trace-output*))
434
435             (etypecase *compile-object*
436               (fasl-file
437                (maybe-mumble "fasl")
438                (fasl-dump-component component
439                                     *code-segment*
440                                     code-length
441                                     trace-table
442                                     fixups
443                                     *compile-object*))
444               (core-object
445                (maybe-mumble "core")
446                (make-core-component component
447                                     *code-segment*
448                                     code-length
449                                     trace-table
450                                     fixups
451                                     *compile-object*))
452               (null))))))
453
454   ;; We are done, so don't bother keeping anything around.
455   (setf (component-info component) nil)
456
457   (values))
458
459 ;;; Return our best guess for whether we will byte compile code
460 ;;; currently being IR1 converted. This is only a guess because the
461 ;;; decision is made on a per-component basis.
462 ;;;
463 ;;; FIXME: This should be called something more mnemonic, e.g.
464 ;;; PROBABLY-BYTE-COMPILING
465 (defun byte-compiling ()
466   (if (eq *byte-compiling* :maybe)
467       (or (eq *byte-compile* t)
468           (policy nil (zerop speed) (<= debug 1)))
469       (and *byte-compile* *byte-compiling*)))
470
471 ;;; Delete components with no external entry points before we try to
472 ;;; generate code. Unreachable closures can cause IR2 conversion to puke on
473 ;;; itself, since it is the reference to the closure which normally causes the
474 ;;; components to be combined. This doesn't really cover all cases...
475 (defun delete-if-no-entries (component)
476   (dolist (fun (component-lambdas component)
477                (delete-component component))
478     (case (functional-kind fun)
479       (:top-level (return))
480       (:external
481        (unless (every #'(lambda (ref)
482                           (eq (block-component (node-block ref))
483                               component))
484                       (leaf-refs fun))
485          (return))))))
486
487 (defun compile-component (component)
488   (let* ((*component-being-compiled* component)
489          (*byte-compiling*
490           (ecase *byte-compile*
491             ((t) t)
492             ((nil) nil)
493             (:maybe
494              (dolist (fun (component-lambdas component) t)
495                (unless (policy (lambda-bind fun)
496                                (zerop speed) (<= debug 1))
497                  (return nil)))))))
498
499     (when sb!xc:*compile-print*
500       ;; MNA: compiler message patch
501       (compiler-mumble "~&; ~:[~;byte ~]compiling ~A: "
502                        *byte-compiling*
503                        (component-name component)))
504
505     (ir1-phases component)
506
507     ;; FIXME: What is MAYBE-MUMBLE for? Do we need it any more?
508     (maybe-mumble "env ")
509     (environment-analyze component)
510     (dfo-as-needed component)
511
512     (delete-if-no-entries component)
513
514     (unless (eq (block-next (component-head component))
515                 (component-tail component))
516       (if *byte-compiling*
517           (byte-compile-component component)
518           (native-compile-component component))))
519
520   (clear-constant-info)
521
522   (when sb!xc:*compile-print*
523     (compiler-mumble "~&"))
524
525   (values))
526 \f
527 ;;;; clearing global data structures
528 ;;;;
529 ;;;; FIXME: Is it possible to get rid of this stuff, getting rid of
530 ;;;; global data structures entirely when possible and consing up the
531 ;;;; others from scratch instead of clearing and reusing them?
532
533 ;;; Clear the INFO in constants in the *FREE-VARIABLES*, etc. In
534 ;;; addition to allowing stuff to be reclaimed, this is required for
535 ;;; correct assignment of constant offsets, since we need to assign a
536 ;;; new offset for each component. We don't clear the FUNCTIONAL-INFO
537 ;;; slots, since they are used to keep track of functions across
538 ;;; component boundaries.
539 (defun clear-constant-info ()
540   (maphash #'(lambda (k v)
541                (declare (ignore k))
542                (setf (leaf-info v) nil))
543            *constants*)
544   (maphash #'(lambda (k v)
545                (declare (ignore k))
546                (when (constant-p v)
547                  (setf (leaf-info v) nil)))
548            *free-variables*)
549   (values))
550
551 ;;; Blow away the REFS for all global variables, and let COMPONENT
552 ;;; be recycled.
553 (defun clear-ir1-info (component)
554   (declare (type component component))
555   (labels ((blast (x)
556              (maphash #'(lambda (k v)
557                           (declare (ignore k))
558                           (when (leaf-p v)
559                             (setf (leaf-refs v)
560                                   (delete-if #'here-p (leaf-refs v)))
561                             (when (basic-var-p v)
562                               (setf (basic-var-sets v)
563                                     (delete-if #'here-p (basic-var-sets v))))))
564                       x))
565            (here-p (x)
566              (eq (block-component (node-block x)) component)))
567     (blast *free-variables*)
568     (blast *free-functions*)
569     (blast *constants*))
570   (values))
571
572 ;;; Clear global variables used by the compiler.
573 ;;;
574 ;;; FIXME: It seems kinda nasty and unmaintainable to have to do this,
575 ;;; and it adds overhead even when people aren't using the compiler.
576 ;;; Perhaps we could make these global vars unbound except when
577 ;;; actually in use, so that this function could go away.
578 (defun clear-stuff (&optional (debug-too t))
579
580   ;; Clear global tables.
581   (when (boundp '*free-functions*)
582     (clrhash *free-functions*)
583     (clrhash *free-variables*)
584     (clrhash *constants*))
585
586   ;; Clear debug counters and tables.
587   (clrhash *seen-blocks*)
588   (clrhash *seen-functions*)
589   (clrhash *list-conflicts-table*)
590
591   (when debug-too
592     (clrhash *continuation-numbers*)
593     (clrhash *number-continuations*)
594     (setq *continuation-number* 0)
595     (clrhash *tn-ids*)
596     (clrhash *id-tns*)
597     (setq *tn-id* 0)
598     (clrhash *label-ids*)
599     (clrhash *id-labels*)
600     (setq *label-id* 0)
601
602     ;; Clear some Pack data structures (for GC purposes only).
603     (assert (not *in-pack*))
604     (dolist (sb *backend-sb-list*)
605       (when (finite-sb-p sb)
606         (fill (finite-sb-live-tns sb) nil))))
607
608   ;; (Note: The CMU CL code used to set CL::*GENSYM-COUNTER* to zero here.
609   ;; Superficially, this seemed harmful -- the user could reasonably be
610   ;; surprised if *GENSYM-COUNTER* turned back to zero when something was
611   ;; compiled. A closer inspection showed that this actually turned out to be
612   ;; harmless in practice, because CLEAR-STUFF was only called from within
613   ;; forms which bound CL::*GENSYM-COUNTER* to zero. However, this means that
614   ;; even though zeroing CL::*GENSYM-COUNTER* here turned out to be harmless in
615   ;; practice, it was also useless in practice. So we don't do it any more.)
616
617   (values))
618 \f
619 ;;;; trace output
620
621 ;;; Print out some useful info about Component to Stream.
622 (defun describe-component (component *standard-output*)
623   (declare (type component component))
624   (format t "~|~%;;;; component: ~S~2%" (component-name component))
625   (print-blocks component)
626   (values))
627
628 (defun describe-ir2-component (component *standard-output*)
629   (format t "~%~|~%;;;; IR2 component: ~S~2%" (component-name component))
630   (format t "entries:~%")
631   (dolist (entry (ir2-component-entries (component-info component)))
632     (format t "~4TL~D: ~S~:[~; [closure]~]~%"
633             (label-id (entry-info-offset entry))
634             (entry-info-name entry)
635             (entry-info-closure-p entry)))
636   (terpri)
637   (pre-pack-tn-stats component *standard-output*)
638   (terpri)
639   (print-ir2-blocks component)
640   (terpri)
641   (values))
642 \f
643 ;;;; file reading
644 ;;;;
645 ;;;; When reading from a file, we have to keep track of some source
646 ;;;; information. We also exploit our ability to back up for printing
647 ;;;; the error context and for recovering from errors.
648 ;;;;
649 ;;;; The interface we provide to this stuff is the stream-oid
650 ;;;; Source-Info structure. The bookkeeping is done as a side-effect
651 ;;;; of getting the next source form.
652
653 ;;; The File-Info structure holds all the source information for a
654 ;;; given file.
655 (defstruct file-info
656   ;; If a file, the truename of the corresponding source file. If from a Lisp
657   ;; form, :LISP, if from a stream, :STREAM.
658   (name (required-argument) :type (or pathname (member :lisp :stream)))
659   ;; The defaulted, but not necessarily absolute file name (i.e. prior to
660   ;; TRUENAME call.)  Null if not a file. This is used to set
661   ;; *COMPILE-FILE-PATHNAME*, and if absolute, is dumped in the debug-info.
662   (untruename nil :type (or pathname null))
663   ;; The file's write date (if relevant.)
664   (write-date nil :type (or unsigned-byte null))
665   ;; This file's FILE-COMMENT, or NIL if none.
666   (comment nil :type (or simple-string null))
667   ;; The source path root number of the first form in this file (i.e. the
668   ;; total number of forms converted previously in this compilation.)
669   (source-root 0 :type unsigned-byte)
670   ;; Parallel vectors containing the forms read out of the file and the file
671   ;; positions that reading of each form started at (i.e. the end of the
672   ;; previous form.)
673   (forms (make-array 10 :fill-pointer 0 :adjustable t) :type (vector t))
674   (positions (make-array 10 :fill-pointer 0 :adjustable t) :type (vector t)))
675
676 ;;; The SOURCE-INFO structure provides a handle on all the source
677 ;;; information for an entire compilation.
678 (defstruct (source-info
679             #-no-ansi-print-object
680             (:print-object (lambda (s stream)
681                              (print-unreadable-object (s stream :type t)))))
682   ;; the UT that compilation started at
683   (start-time (get-universal-time) :type unsigned-byte)
684   ;; a list of the FILE-INFO structures for this compilation
685   (files nil :type list)
686   ;; the tail of the FILES for the file we are currently reading
687   (current-file nil :type list)
688   ;; the stream that we are using to read the CURRENT-FILE, or NIL if
689   ;; no stream has been opened yet
690   (stream nil :type (or stream null)))
691
692 ;;; Given a list of pathnames, return a SOURCE-INFO structure.
693 (defun make-file-source-info (files)
694   (declare (list files))
695   (let ((file-info
696          (mapcar (lambda (x)
697                    (make-file-info :name (truename x)
698                                    :untruename x
699                                    :write-date (file-write-date x)))
700                  files)))
701
702     (make-source-info :files file-info
703                       :current-file file-info)))
704
705 ;;; Return a SOURCE-INFO to describe the incremental compilation of
706 ;;; FORM. Also used by SB!EVAL:INTERNAL-EVAL.
707 (defun make-lisp-source-info (form)
708   (make-source-info
709    :start-time (get-universal-time)
710    :files (list (make-file-info :name :lisp
711                                 :forms (vector form)
712                                 :positions '#(0)))))
713
714 ;;; Return a SOURCE-INFO which will read from Stream.
715 (defun make-stream-source-info (stream)
716   (let ((files (list (make-file-info :name :stream))))
717     (make-source-info
718      :files files
719      :current-file files
720      :stream stream)))
721
722 ;;; Print an error message for a non-EOF error on STREAM. OLD-POS is a
723 ;;; preceding file position that hopefully comes before the beginning
724 ;;; of the line. Of course, this only works on streams that support
725 ;;; the file-position operation.
726 (defun normal-read-error (stream old-pos condition)
727   (declare (type stream stream) (type unsigned-byte old-pos))
728   (let ((pos (file-position stream)))
729     (file-position stream old-pos)
730     (let ((start old-pos))
731       (loop
732         (let ((line (read-line stream nil))
733               (end (file-position stream)))
734           (when (>= end pos)
735             ;; FIXME: READER-ERROR also prints the file position. Do we really
736             ;; need to try to give position information here?
737             (compiler-abort "read error at ~D:~% \"~A/\\~A\"~%~A"
738                             pos
739                             (string-left-trim "         "
740                                               (subseq line 0 (- pos start)))
741                             (subseq line (- pos start))
742                             condition)
743             (return))
744           (setq start end)))))
745   (values))
746
747 ;;; Back STREAM up to the position Pos, then read a form with
748 ;;; *READ-SUPPRESS* on, discarding the result. If an error happens
749 ;;; during this read, then bail out using COMPILER-ERROR (fatal in
750 ;;; this context).
751 (defun ignore-error-form (stream pos)
752   (declare (type stream stream) (type unsigned-byte pos))
753   (file-position stream pos)
754   (handler-case (let ((*read-suppress* t))
755                   (read stream))
756     (error (condition)
757       (declare (ignore condition))
758       (compiler-error "unable to recover from read error"))))
759
760 ;;; Print an error message giving some context for an EOF error. We
761 ;;; print the first line after POS that contains #\" or #\(, or
762 ;;; lacking that, the first non-empty line.
763 (defun unexpected-eof-error (stream pos condition)
764   (declare (type stream stream) (type unsigned-byte pos))
765   (let ((res nil))
766     (file-position stream pos)
767     (loop
768       (let ((line (read-line stream nil nil)))
769         (unless line (return))
770         (when (or (find #\" line) (find #\( line))
771           (setq res line)
772           (return))
773         (unless (or res (zerop (length line)))
774           (setq res line))))
775     (compiler-abort "read error in form starting at ~D:~%~@[ \"~A\"~%~]~A"
776                     pos
777                     res
778                     condition))
779   (file-position stream (file-length stream))
780   (values))
781
782 ;;; Read a form from STREAM, returning EOF at EOF. If a read error
783 ;;; happens, then attempt to recover if possible, returning a proxy
784 ;;; error form.
785 ;;;
786 ;;; FIXME: This seems like quite a lot of complexity, and it seems
787 ;;; impossible to get it quite right. (E.g. the `(CERROR ..) form
788 ;;; returned here won't do the right thing if it's not in a position
789 ;;; for an executable form.) I think it might be better to just stop
790 ;;; trying to recover from read errors, punting all this noise
791 ;;; (including UNEXPECTED-EOF-ERROR and IGNORE-ERROR-FORM) and doing a
792 ;;; COMPILER-ABORT instead.
793 (defun careful-read (stream eof pos)
794   (handler-case (read stream nil eof)
795     (error (condition)
796       (let ((new-pos (file-position stream)))
797         (cond ((= new-pos (file-length stream))
798                (unexpected-eof-error stream pos condition))
799               (t
800                (normal-read-error stream pos condition)
801                (ignore-error-form stream pos))))
802       '(cerror "Skip this form."
803                "compile-time read error"))))
804
805 ;;; If Stream is present, return it, otherwise open a stream to the
806 ;;; current file. There must be a current file. When we open a new
807 ;;; file, we also reset *PACKAGE* and policy. This gives the effect of
808 ;;; rebinding around each file.
809 ;;;
810 ;;; FIXME: Since we now do the standard ANSI thing of only one file
811 ;;; per compile (unlike the CMU CL extended COMPILE-FILE) can't this
812 ;;; complexity (including ADVANCE-SOURCE-FILE) go away?
813 (defun get-source-stream (info)
814   (declare (type source-info info))
815   (cond ((source-info-stream info))
816         (t
817          (setq *package* *initial-package*)
818          (setq *default-cookie* (copy-cookie *initial-cookie*))
819          (setq *default-interface-cookie*
820                (copy-cookie *initial-interface-cookie*))
821          (let* ((finfo (first (source-info-current-file info)))
822                 (name (file-info-name finfo)))
823            (setq sb!xc:*compile-file-truename* name)
824            (setq sb!xc:*compile-file-pathname* (file-info-untruename finfo))
825            (setf (source-info-stream info)
826                  (open name :direction :input))))))
827
828 ;;; Close the stream in INFO if it is open.
829 (defun close-source-info (info)
830   (declare (type source-info info))
831   (let ((stream (source-info-stream info)))
832     (when stream (close stream)))
833   (setf (source-info-stream info) nil)
834   (values))
835
836 ;;; Advance INFO to the next source file. If there is no next source
837 ;;; file, return NIL, otherwise T.
838 (defun advance-source-file (info)
839   (declare (type source-info info))
840   (close-source-info info)
841   (let ((prev (pop (source-info-current-file info))))
842     (if (source-info-current-file info)
843         (let ((current (first (source-info-current-file info))))
844           (setf (file-info-source-root current)
845                 (+ (file-info-source-root prev)
846                    (length (file-info-forms prev))))
847           t)
848         nil)))
849
850 ;;; Read the sources from the source files and process them.
851 (defun process-sources (info)
852   (let* ((file (first (source-info-current-file info)))
853          (stream (get-source-stream info)))
854     (loop
855      (let* ((pos (file-position stream))
856             (eof '(*eof*))
857             (form (careful-read stream eof pos)))
858        (if (eq form eof)
859          (return)
860          (let* ((forms (file-info-forms file))
861                 (current-idx (+ (fill-pointer forms)
862                                 (file-info-source-root file))))
863            (vector-push-extend form forms)
864            (vector-push-extend pos (file-info-positions file))
865            (clrhash *source-paths*)
866            (find-source-paths form current-idx)
867            (process-top-level-form form
868                                    `(original-source-start 0 ,current-idx))))))
869     (when (advance-source-file info)
870       (process-sources info))))
871
872 ;;; Return the FILE-INFO describing the INDEX'th form.
873 (defun find-file-info (index info)
874   (declare (type index index) (type source-info info))
875   (dolist (file (source-info-files info))
876     (when (> (+ (length (file-info-forms file))
877                 (file-info-source-root file))
878              index)
879       (return file))))
880
881 ;;; Return the INDEX'th source form read from INFO and the position
882 ;;; where it was read.
883 (defun find-source-root (index info)
884   (declare (type source-info info) (type index index))
885   (let* ((file (find-file-info index info))
886          (idx (- index (file-info-source-root file))))
887     (values (aref (file-info-forms file) idx)
888             (aref (file-info-positions file) idx))))
889 \f
890 ;;;; top-level form processing
891
892 ;;; This is called by top-level form processing when we are ready to
893 ;;; actually compile something. If *BLOCK-COMPILE* is T, then we still
894 ;;; convert the form, but delay compilation, pushing the result on
895 ;;; *TOP-LEVEL-LAMBDAS* instead.
896 (defun convert-and-maybe-compile (form path)
897   (declare (list path))
898   (let* ((*lexenv* (make-lexenv :cookie *default-cookie*
899                                 :interface-cookie *default-interface-cookie*))
900          (tll (ir1-top-level form path nil)))
901     (cond ((eq *block-compile* t) (push tll *top-level-lambdas*))
902           (t (compile-top-level (list tll) nil)))))
903
904 ;;; Process a PROGN-like portion of a top-level form. Forms is a list of
905 ;;; the forms, and Path is source path of the form they came out of.
906 (defun process-top-level-progn (forms path)
907   (declare (list forms) (list path))
908   (dolist (form forms)
909     (process-top-level-form form path)))
910
911 ;;; Macroexpand form in the current environment with an error handler.
912 ;;; We only expand one level, so that we retain all the intervening
913 ;;; forms in the source path.
914 (defun preprocessor-macroexpand (form)
915   (handler-case (sb!xc:macroexpand-1 form *lexenv*)
916     (error (condition)
917        (compiler-error "(during macroexpansion)~%~A" condition))))
918
919 ;;; Process a top-level use of LOCALLY. We parse declarations and then
920 ;;; recursively process the body.
921 ;;;
922 ;;; Binding *DEFAULT-xxx-COOKIE* is pretty much of a hack, since it
923 ;;; causes LOCALLY to "capture" enclosed proclamations. It is
924 ;;; necessary because CONVERT-AND-MAYBE-COMPILE uses the value of
925 ;;; *DEFAULT-COOKIE* as the policy. The need for this hack is due to
926 ;;; the quirk that there is no way to represent in a cookie that an
927 ;;; optimize quality came from the default.
928 (defun process-top-level-locally (form path)
929   (declare (list path))
930   (multiple-value-bind (forms decls) (sb!sys:parse-body (cdr form) nil)
931     (let* ((*lexenv*
932             (process-decls decls nil nil (make-continuation)))
933            (*default-cookie* (lexenv-cookie *lexenv*))
934            (*default-interface-cookie* (lexenv-interface-cookie *lexenv*)))
935       (process-top-level-progn forms path))))
936
937 ;;; Stash file comment in the FILE-INFO structure.
938 (defun process-file-comment (form)
939   (unless (and (proper-list-of-length-p form 2)
940                (stringp (second form)))
941     (compiler-error "bad FILE-COMMENT form: ~S" form))
942   (let ((file (first (source-info-current-file *source-info*))))
943     (cond ((file-info-comment file)
944             ;; MNA: compiler message patch
945             (pprint-logical-block (*error-output* nil :per-line-prefix "; ")
946               (compiler-warning "Ignoring extra file comment:~%  ~S." form)))
947           (t
948            (let ((comment (coerce (second form) 'simple-string)))
949              (setf (file-info-comment file) comment)
950              (when sb!xc:*compile-verbose*
951                ;; MNA: compiler message patch
952                (compiler-mumble "~&; FILE-COMMENT: ~A~2&" comment)))))))
953
954 ;;; Force any pending top-level forms to be compiled and dumped so that they
955 ;;; will be evaluated in the correct package environment. Dump the form to be
956 ;;; evaled at (cold) load time, and if EVAL is true, eval the form immediately.
957 (defun process-cold-load-form (form path eval)
958   (let ((object *compile-object*))
959     (etypecase object
960       (fasl-file
961        (compile-top-level-lambdas () t)
962        (fasl-dump-cold-load-form form object))
963       ((or null core-object)
964        (convert-and-maybe-compile form path)))
965     (when eval
966       (eval form))))
967
968 (declaim (special *compiler-error-bailout*))
969
970 ;;; Process a top-level FORM with the specified source PATH.
971 ;;;  * If this is a magic top-level form, then do stuff.
972 ;;;  * If this is a macro, then expand it.
973 ;;;  * Otherwise, just compile it.
974 (defun process-top-level-form (form path)
975
976   (declare (list path))
977
978   (catch 'process-top-level-form-error-abort
979     (let* ((path (or (gethash form *source-paths*) (cons form path)))
980            (*compiler-error-bailout*
981             #'(lambda ()
982                 (convert-and-maybe-compile
983                  `(error "execution of a form compiled with errors:~% ~S"
984                          ',form)
985                  path)
986                 (throw 'process-top-level-form-error-abort nil))))
987       (if (atom form)
988           (convert-and-maybe-compile form path)
989           (case (car form)
990             ;; FIXME: It's not clear to me why we would want this
991             ;; special case; it might have been needed for some
992             ;; variation of the old GENESIS system, but it certainly
993             ;; doesn't seem to be needed for ours. Sometime after the
994             ;; system is running I'd like to remove it tentatively and
995             ;; see whether anything breaks, and if nothing does break,
996             ;; remove it permanently. (And if we *do* want special
997             ;; treatment of all these, we probably want to treat WARN
998             ;; the same way..)
999             ((error cerror break signal)
1000              (process-cold-load-form form path nil))
1001             ;; FIXME: ANSI seems to encourage things like DEFSTRUCT to
1002             ;; be done with EVAL-WHEN, without this kind of one-off
1003             ;; compiler magic.
1004             (sb!kernel:%compiler-defstruct
1005              (convert-and-maybe-compile form path)
1006              (compile-top-level-lambdas () t))
1007             ((eval-when)
1008              (unless (>= (length form) 2)
1009                (compiler-error "EVAL-WHEN form is too short: ~S" form))
1010              (do-eval-when-stuff
1011               (cadr form) (cddr form)
1012               #'(lambda (forms)
1013                   (process-top-level-progn forms path))))
1014             ((macrolet)
1015              (unless (>= (length form) 2)
1016                (compiler-error "MACROLET form is too short: ~S" form))
1017              (do-macrolet-stuff
1018               (cadr form)
1019               #'(lambda ()
1020                   (process-top-level-progn (cddr form) path))))
1021             (locally (process-top-level-locally form path))
1022             (progn (process-top-level-progn (cdr form) path))
1023             (file-comment (process-file-comment form))
1024             (t
1025              (let* ((uform (uncross form))
1026                     (exp (preprocessor-macroexpand uform)))
1027                (if (eq exp uform)
1028                    (convert-and-maybe-compile uform path)
1029                    (process-top-level-form exp path))))))))
1030
1031   (values))
1032 \f
1033 ;;;; load time value support
1034 ;;;;
1035 ;;;; (See EMIT-MAKE-LOAD-FORM.)
1036
1037 ;;; Returns T iff we are currently producing a fasl-file and hence
1038 ;;; constants need to be dumped carefully.
1039 (defun producing-fasl-file ()
1040   (unless *converting-for-interpreter*
1041     (fasl-file-p *compile-object*)))
1042
1043 ;;; Compile FORM and arrange for it to be called at load-time. Return
1044 ;;; the dumper handle and our best guess at the type of the object.
1045 (defun compile-load-time-value
1046        (form &optional
1047              (name (let ((*print-level* 2) (*print-length* 3))
1048                      (format nil "load time value of ~S"
1049                              (if (and (listp form)
1050                                       (eq (car form) 'make-value-cell))
1051                                  (second form)
1052                                  form)))))
1053   (let ((lambda (compile-load-time-stuff form name t)))
1054     (values
1055      (fasl-dump-load-time-value-lambda lambda *compile-object*)
1056      (let ((type (leaf-type lambda)))
1057        (if (function-type-p type)
1058            (single-value-type (function-type-returns type))
1059            *wild-type*)))))
1060
1061 ;;; Compile the FORMS and arrange for them to be called (for effect,
1062 ;;; not value) at load time.
1063 (defun compile-make-load-form-init-forms (forms name)
1064   (let ((lambda (compile-load-time-stuff `(progn ,@forms) name nil)))
1065     (fasl-dump-top-level-lambda-call lambda *compile-object*)))
1066
1067 ;;; Does the actual work of COMPILE-LOAD-TIME-VALUE or
1068 ;;; COMPILE-MAKE-LOAD-FORM- INIT-FORMS.
1069 (defun compile-load-time-stuff (form name for-value)
1070   (with-ir1-namespace
1071    (let* ((*lexenv* (make-null-lexenv))
1072           (lambda (ir1-top-level form *current-path* for-value)))
1073      (setf (leaf-name lambda) name)
1074      (compile-top-level (list lambda) t)
1075      lambda)))
1076
1077 ;;; Called by COMPILE-TOP-LEVEL when it was pased T for
1078 ;;; LOAD-TIME-VALUE-P (which happens in COMPILE-LOAD-TIME-STUFF). We
1079 ;;; don't try to combine this component with anything else and frob
1080 ;;; the name. If not in a :TOP-LEVEL component, then don't bother
1081 ;;; compiling, because it was merged with a run-time component.
1082 (defun compile-load-time-value-lambda (lambdas)
1083   (assert (null (cdr lambdas)))
1084   (let* ((lambda (car lambdas))
1085          (component (block-component (node-block (lambda-bind lambda)))))
1086     (when (eq (component-kind component) :top-level)
1087       (setf (component-name component) (leaf-name lambda))
1088       (compile-component component)
1089       (clear-ir1-info component))))
1090
1091 ;;; The entry point for MAKE-LOAD-FORM support. When IR1 conversion
1092 ;;; finds a constant structure, it invokes this to arrange for proper
1093 ;;; dumping. If it turns out that the constant has already been
1094 ;;; dumped, then we don't need to do anything.
1095 ;;;
1096 ;;; If the constant hasn't been dumped, then we check to see whether
1097 ;;; we are in the process of creating it. We detect this by
1098 ;;; maintaining the special *CONSTANTS-BEING-CREATED* as a list of all
1099 ;;; the constants we are in the process of creating. Actually, each
1100 ;;; entry is a list of the constant and any init forms that need to be
1101 ;;; processed on behalf of that constant.
1102 ;;;
1103 ;;; It's not necessarily an error for this to happen. If we are
1104 ;;; processing the init form for some object that showed up *after*
1105 ;;; the original reference to this constant, then we just need to
1106 ;;; defer the processing of that init form. To detect this, we
1107 ;;; maintain *CONSTANTS-CREATED-SINCE-LAST-INIT* as a list of the
1108 ;;; constants created since the last time we started processing an
1109 ;;; init form. If the constant passed to emit-make-load-form shows up
1110 ;;; in this list, then there is a circular chain through creation
1111 ;;; forms, which is an error.
1112 ;;;
1113 ;;; If there is some intervening init form, then we blow out of
1114 ;;; processing it by throwing to the tag PENDING-INIT. The value we
1115 ;;; throw is the entry from *CONSTANTS-BEING-CREATED*. This is so the
1116 ;;; offending init form can be tacked onto the init forms for the
1117 ;;; circular object.
1118 ;;;
1119 ;;; If the constant doesn't show up in *CONSTANTS-BEING-CREATED*, then
1120 ;;; we have to create it. We call MAKE-LOAD-FORM and check to see
1121 ;;; whether the creation form is the magic value
1122 ;;; :JUST-DUMP-IT-NORMALLY. If it is, then we don't do anything. The
1123 ;;; dumper will eventually get its hands on the object and use the
1124 ;;; normal structure dumping noise on it.
1125 ;;;
1126 ;;; Otherwise, we bind *CONSTANTS-BEING-CREATED* and
1127 ;;; *CONSTANTS-CREATED-SINCE- LAST-INIT* and compile the creation form
1128 ;;; much the way LOAD-TIME-VALUE does. When this finishes, we tell the
1129 ;;; dumper to use that result instead whenever it sees this constant.
1130 ;;;
1131 ;;; Now we try to compile the init form. We bind
1132 ;;; *CONSTANTS-CREATED-SINCE- LAST-INIT* to NIL and compile the init
1133 ;;; form (and any init forms that were added because of circularity
1134 ;;; detection). If this works, great. If not, we add the init forms to
1135 ;;; the init forms for the object that caused the problems and let it
1136 ;;; deal with it.
1137 (defvar *constants-being-created* nil)
1138 (defvar *constants-created-since-last-init* nil)
1139 ;;; FIXME: Shouldn't these^ variables be bound in LET forms?
1140 (defun emit-make-load-form (constant)
1141   (assert (fasl-file-p *compile-object*))
1142   (unless (or (fasl-constant-already-dumped constant *compile-object*)
1143               ;; KLUDGE: This special hack is because I was too lazy
1144               ;; to rework DEF!STRUCT so that the MAKE-LOAD-FORM
1145               ;; function of LAYOUT returns nontrivial forms when
1146               ;; building the cross-compiler but :IGNORE-IT when
1147               ;; cross-compiling or running under the target Lisp. --
1148               ;; WHN 19990914
1149               #+sb-xc-host (typep constant 'layout))
1150     (let ((circular-ref (assoc constant *constants-being-created* :test #'eq)))
1151       (when circular-ref
1152         (when (find constant *constants-created-since-last-init* :test #'eq)
1153           (throw constant t))
1154         (throw 'pending-init circular-ref)))
1155     (multiple-value-bind (creation-form init-form)
1156         (handler-case
1157             (sb!xc:make-load-form constant (make-null-lexenv))
1158           (error (condition)
1159                  (compiler-error "(while making load form for ~S)~%~A"
1160                                  constant
1161                                  condition)))
1162       (case creation-form
1163         (:just-dump-it-normally
1164          (fasl-validate-structure constant *compile-object*)
1165          t)
1166         (:ignore-it
1167          nil)
1168         (t
1169          (compile-top-level-lambdas () t)
1170          (when (fasl-constant-already-dumped constant *compile-object*)
1171            (return-from emit-make-load-form nil))
1172          (let* ((name (let ((*print-level* 1) (*print-length* 2))
1173                         (with-output-to-string (stream)
1174                           (write constant :stream stream))))
1175                 (info (if init-form
1176                           (list constant name init-form)
1177                           (list constant))))
1178            (let ((*constants-being-created*
1179                   (cons info *constants-being-created*))
1180                  (*constants-created-since-last-init*
1181                   (cons constant *constants-created-since-last-init*)))
1182              (when
1183                  (catch constant
1184                    (fasl-note-handle-for-constant
1185                     constant
1186                     (compile-load-time-value
1187                      creation-form
1188                      (format nil "creation form for ~A" name))
1189                     *compile-object*)
1190                    nil)
1191                (compiler-error "circular references in creation form for ~S"
1192                                constant)))
1193            (when (cdr info)
1194              (let* ((*constants-created-since-last-init* nil)
1195                     (circular-ref
1196                      (catch 'pending-init
1197                        (loop for (name form) on (cdr info) by #'cddr
1198                          collect name into names
1199                          collect form into forms
1200                          finally
1201                          (compile-make-load-form-init-forms
1202                           forms
1203                           (format nil "init form~:[~;s~] for ~{~A~^, ~}"
1204                                   (cdr forms) names)))
1205                        nil)))
1206                (when circular-ref
1207                  (setf (cdr circular-ref)
1208                        (append (cdr circular-ref) (cdr info))))))))))))
1209 \f
1210 ;;;; COMPILE-FILE
1211
1212 ;;; We build a list of top-level lambdas, and then periodically smash
1213 ;;; them together into a single component and compile it.
1214 (defvar *pending-top-level-lambdas*)
1215
1216 ;;; The maximum number of top-level lambdas we put in a single
1217 ;;; top-level component.
1218 ;;;
1219 ;;; CMU CL 18b used this nontrivially by default (setting it to 10)
1220 ;;; but consequently suffered from the inability to execute some
1221 ;;; troublesome constructs correctly, e.g. inability to load a fasl
1222 ;;; file compiled from the source file
1223 ;;;   (defpackage "FOO" (:use "CL"))
1224 ;;;   (print 'foo::bar)
1225 ;;; because it would dump data-setup fops (including a FOP-PACKAGE for
1226 ;;; "FOO") for the second form before dumping the the code in the
1227 ;;; first form, or the fop to execute the code in the first form. By
1228 ;;; setting this value to 0 by default, we avoid this badness. This
1229 ;;; increases the number of toplevel form functions, and so increases
1230 ;;; the size of object files.
1231 ;;;
1232 ;;; The variable is still supported because when we are compiling the
1233 ;;; SBCL system itself, which is known not contain any troublesome
1234 ;;; constructs, we can set it to a nonzero value, which reduces the
1235 ;;; number of toplevel form objects, reducing the peak memory usage in
1236 ;;; GENESIS, which is desirable, since at least for SBCL version
1237 ;;; 0.6.7, this is the high water mark for memory usage during system
1238 ;;; construction.
1239 (defparameter *top-level-lambda-max* 0)
1240
1241 (defun object-call-top-level-lambda (tll)
1242   (declare (type functional tll))
1243   (let ((object *compile-object*))
1244     (etypecase object
1245       (fasl-file
1246        (fasl-dump-top-level-lambda-call tll object))
1247       (core-object
1248        (core-call-top-level-lambda tll object))
1249       (null))))
1250
1251 ;;; Add LAMBDAS to the pending lambdas. If this leaves more than
1252 ;;; *TOP-LEVEL-LAMBDA-MAX* lambdas in the list, or if FORCE-P is true,
1253 ;;; then smash the lambdas into a single component, compile it, and
1254 ;;; call the resulting function.
1255 (defun sub-compile-top-level-lambdas (lambdas force-p)
1256   (declare (list lambdas))
1257   (setq *pending-top-level-lambdas*
1258         (append *pending-top-level-lambdas* lambdas))
1259   (let ((pending *pending-top-level-lambdas*))
1260     (when (and pending
1261                (or (> (length pending) *top-level-lambda-max*)
1262                    force-p))
1263       (multiple-value-bind (component tll) (merge-top-level-lambdas pending)
1264         (setq *pending-top-level-lambdas* ())
1265         (let ((*byte-compile* (if (eq *byte-compile* :maybe)
1266                                   *byte-compile-top-level*
1267                                   *byte-compile*)))
1268           (compile-component component))
1269         (clear-ir1-info component)
1270         (object-call-top-level-lambda tll))))
1271   (values))
1272
1273 ;;; Compile top-level code and call the top-level lambdas. We pick off
1274 ;;; top-level lambdas in non-top-level components here, calling
1275 ;;; SUB-c-t-l-l on each subsequence of normal top-level lambdas.
1276 (defun compile-top-level-lambdas (lambdas force-p)
1277   (declare (list lambdas))
1278   (let ((len (length lambdas)))
1279     (flet ((loser (start)
1280              (or (position-if #'(lambda (x)
1281                                   (not (eq (component-kind
1282                                             (block-component
1283                                              (node-block
1284                                               (lambda-bind x))))
1285                                            :top-level)))
1286                               lambdas
1287                               :start start)
1288                  len)))
1289       (do* ((start 0 (1+ loser))
1290             (loser (loser start) (loser start)))
1291            ((>= start len)
1292             (when force-p
1293               (sub-compile-top-level-lambdas nil t)))
1294         (sub-compile-top-level-lambdas (subseq lambdas start loser)
1295                                        (or force-p (/= loser len)))
1296         (unless (= loser len)
1297           (object-call-top-level-lambda (elt lambdas loser))))))
1298   (values))
1299
1300 ;;; Compile LAMBDAS (a list of the lambdas for top-level forms) into
1301 ;;; the object file. We loop doing local call analysis until it
1302 ;;; converges, since a single pass might miss something due to
1303 ;;; components being joined by LET conversion.
1304 ;;;
1305 ;;; LOAD-TIME-VALUE-P seems to control whether it's MAKE-LOAD-FORM and
1306 ;;; COMPILE-LOAD-TIME-VALUE stuff. -- WHN 20000201
1307 (defun compile-top-level (lambdas load-time-value-p)
1308   (declare (list lambdas))
1309   (maybe-mumble "locall ")
1310   (loop
1311     (let ((did-something nil))
1312       (dolist (lambda lambdas)
1313         (let* ((component (block-component (node-block (lambda-bind lambda))))
1314                (*all-components* (list component)))
1315           (when (component-new-functions component)
1316             (setq did-something t)
1317             (local-call-analyze component))))
1318       (unless did-something (return))))
1319
1320   (maybe-mumble "IDFO ")
1321   (multiple-value-bind (components top-components hairy-top)
1322       (find-initial-dfo lambdas)
1323     (let ((*all-components* (append components top-components))
1324           (top-level-closure nil))
1325       (when *check-consistency*
1326         (maybe-mumble "[check]~%")
1327         (check-ir1-consistency *all-components*))
1328
1329       (dolist (component (append hairy-top top-components))
1330         (when (pre-environment-analyze-top-level component)
1331           (setq top-level-closure t)))
1332
1333       (let ((*byte-compile*
1334              (if (and top-level-closure (eq *byte-compile* :maybe))
1335                  nil
1336                  *byte-compile*)))
1337         (dolist (component components)
1338           (compile-component component)
1339           (when (replace-top-level-xeps component)
1340             (setq top-level-closure t)))
1341         
1342         (when *check-consistency*
1343           (maybe-mumble "[check]~%")
1344           (check-ir1-consistency *all-components*))
1345         
1346         (if load-time-value-p
1347             (compile-load-time-value-lambda lambdas)
1348             (compile-top-level-lambdas lambdas top-level-closure)))
1349
1350       (dolist (component components)
1351         (clear-ir1-info component))
1352       (clear-stuff)))
1353   (values))
1354
1355 ;;; Actually compile any stuff that has been queued up for block
1356 ;;; compilation.
1357 (defun finish-block-compilation ()
1358   (when *block-compile*
1359     (when *top-level-lambdas*
1360       (compile-top-level (nreverse *top-level-lambdas*) nil)
1361       (setq *top-level-lambdas* ()))
1362     (setq *block-compile* nil)
1363     (setq *entry-points* nil)))
1364
1365 ;;; Read all forms from INFO and compile them, with output to OBJECT.
1366 ;;; Return (VALUES NIL WARNINGS-P FAILURE-P).
1367 (defun sub-compile-file (info &optional d-s-info)
1368   (declare (type source-info info))
1369   (let* (;; These are bound in WITH-COMPILATION-UNIT now. -- WHN 20000308
1370          #+nil (*compiler-error-count* 0)
1371          #+nil (*compiler-warning-count* 0)
1372          #+nil (*compiler-style-warning-count* 0)
1373          #+nil (*compiler-note-count* 0)
1374          (*block-compile* *block-compile-argument*)
1375          (*package* (sane-package))
1376          (*initial-package* (sane-package))
1377          (*initial-cookie* *default-cookie*)
1378          (*initial-interface-cookie* *default-interface-cookie*)
1379          (*default-cookie* (copy-cookie *initial-cookie*))
1380          (*default-interface-cookie*
1381           (copy-cookie *initial-interface-cookie*))
1382          (*lexenv* (make-null-lexenv))
1383          (*converting-for-interpreter* nil)
1384          (*source-info* info)
1385          (sb!xc:*compile-file-pathname* nil)
1386          (sb!xc:*compile-file-truename* nil)
1387          (*top-level-lambdas* ())
1388          (*pending-top-level-lambdas* ())
1389          (*compiler-error-bailout*
1390           #'(lambda ()
1391               (compiler-mumble
1392                ;; MNA: compiler message patch
1393                "~2&; fatal error, aborting compilation~%")
1394               (return-from sub-compile-file (values nil t t))))
1395          (*current-path* nil)
1396          (*last-source-context* nil)
1397          (*last-original-source* nil)
1398          (*last-source-form* nil)
1399          (*last-format-string* nil)
1400          (*last-format-args* nil)
1401          (*last-message-count* 0)
1402          (*info-environment* (or *backend-info-environment*
1403                                  *info-environment*))
1404          (*gensym-counter* 0))
1405     (with-compilation-values
1406       (sb!xc:with-compilation-unit ()
1407         (clear-stuff)
1408
1409         (process-sources info)
1410
1411         (finish-block-compilation)
1412         (compile-top-level-lambdas () t)
1413         (let ((object *compile-object*))
1414           (etypecase object
1415             (fasl-file (fasl-dump-source-info info object))
1416             (core-object (fix-core-source-info info object d-s-info))
1417             (null)))
1418         nil))))
1419
1420 ;;; Return a list of pathnames for the named files. All the files must
1421 ;;; exist.
1422 (defun verify-source-files (stuff)
1423   (let* ((stuff (if (listp stuff) stuff (list stuff)))
1424          (default-host (make-pathname
1425                         :host (pathname-host (pathname (first stuff))))))
1426     (flet ((try-with-type (path type error-p)
1427              (let ((new (merge-pathnames
1428                          path (make-pathname :type type
1429                                              :defaults default-host))))
1430                (if (probe-file new)
1431                    new
1432                    (and error-p (truename new))))))
1433       (unless stuff
1434         (error "can't compile with no source files"))
1435       (mapcar #'(lambda (x)
1436                   (let ((x (pathname x)))
1437                     (cond ((typep x 'logical-pathname)
1438                            (try-with-type x "LISP" t))
1439                           ((probe-file x) x)
1440                           ((try-with-type x "lisp"  nil))
1441                           ((try-with-type x "lisp"  t)))))
1442               stuff))))
1443
1444 (defun elapsed-time-to-string (tsec)
1445   (multiple-value-bind (tmin sec) (truncate tsec 60)
1446     (multiple-value-bind (thr min) (truncate tmin 60)
1447       (format nil "~D:~2,'0D:~2,'0D" thr min sec))))
1448
1449 ;;; Print some junk at the beginning and end of compilation.
1450 (defun start-error-output (source-info)
1451   (declare (type source-info source-info))
1452   (dolist (x (source-info-files source-info))
1453     ;; MNA: compiler message patch
1454     (compiler-mumble "~&; compiling file ~S (written ~A):~%"
1455                      (namestring (file-info-name x))
1456                      (sb!int:format-universal-time nil
1457                                                    (file-info-write-date x)
1458                                                    :style :government
1459                                                    :print-weekday nil
1460                                                    :print-timezone nil)))
1461   (values))
1462
1463 (defun finish-error-output (source-info won)
1464   (declare (type source-info source-info))
1465   ;; MNA: compiler message patch
1466   (compiler-mumble "~&; compilation ~:[aborted after~;finished in~] ~A~&"
1467                    won
1468                    (elapsed-time-to-string
1469                     (- (get-universal-time)
1470                        (source-info-start-time source-info))))
1471   (values))
1472
1473 ;;; Open some files and call SUB-COMPILE-FILE. If something unwinds
1474 ;;; out of the compile, then abort the writing of the output file, so
1475 ;;; we don't overwrite it with known garbage.
1476 (defun sb!xc:compile-file
1477     (source
1478      &key
1479      (output-file t) ; FIXME: ANSI says this should be a pathname designator.
1480      ;; FIXME: ANSI doesn't seem to say anything about
1481      ;; *COMPILE-VERBOSE* and *COMPILE-PRINT* being rebound by this
1482      ;; function..
1483      ((:verbose sb!xc:*compile-verbose*) sb!xc:*compile-verbose*)
1484      ((:print sb!xc:*compile-print*) sb!xc:*compile-print*)
1485      (external-format :default)
1486      ((:block-compile *block-compile-argument*) nil)
1487      ((:entry-points *entry-points*) nil)
1488      ((:byte-compile *byte-compile*) *byte-compile-default*))
1489   #!+sb-doc
1490   "Compile SOURCE, producing a corresponding FASL file. 
1491    :Output-File
1492       The name of the fasl to output, NIL for none, T for the default.
1493    :Block-Compile
1494       Determines whether multiple functions are compiled together as a unit,
1495       resolving function references at compile time. NIL means that global
1496       function names are never resolved at compilation time.
1497    :Entry-Points
1498       This specifies a list of function names for functions in the file(s) that
1499       must be given global definitions. This only applies to block
1500       compilation. If the value is NIL (the default) then all functions
1501       will be globally defined.
1502    :Byte-Compile {T | NIL | :MAYBE}
1503       Determines whether to compile into interpreted byte code instead of
1504       machine instructions. Byte code is several times smaller, but much
1505       slower. If :MAYBE, then only byte-compile when SPEED is 0 and
1506       DEBUG <= 1. The default is the value of SB-EXT:*BYTE-COMPILE-DEFAULT*,
1507       which is initially :MAYBE."
1508   (unless (eq external-format :default)
1509     (error "Non-:DEFAULT EXTERNAL-FORMAT values are not supported."))
1510   (let* ((fasl-file nil)
1511          (output-file-name nil)
1512          (compile-won nil)
1513          (warnings-p nil)
1514          (failure-p t) ; T in case error keeps this from being set later
1515
1516          ;; KLUDGE: The listifying and unlistifying in the next calls
1517          ;; is to interface to old CMU CL code which accepted and
1518          ;; returned lists of multiple source files. It would be
1519          ;; cleaner to redo VERIFY-SOURCE-FILES and as
1520          ;; VERIFY-SOURCE-FILE, accepting a single source file, and
1521          ;; do a similar transformation on MAKE-FILE-SOURCE-INFO too.
1522          ;; -- WHN 20000201
1523          (source (first (verify-source-files (list source))))
1524          (source-info (make-file-source-info (list source))))
1525     (unwind-protect
1526         (progn
1527           (when output-file
1528             (setq output-file-name
1529                   (sb!xc:compile-file-pathname source
1530                                                :output-file output-file
1531                                                :byte-compile *byte-compile*))
1532             (setq fasl-file
1533                   (open-fasl-file output-file-name
1534                                   (namestring source)
1535                                   (eq *byte-compile* t))))
1536
1537           (when sb!xc:*compile-verbose*
1538             (start-error-output source-info))
1539           (let ((*compile-object* fasl-file)
1540                 dummy)
1541             (multiple-value-setq (dummy warnings-p failure-p)
1542               (sub-compile-file source-info)))
1543           (setq compile-won t))
1544
1545       (close-source-info source-info)
1546
1547       (when fasl-file
1548         (close-fasl-file fasl-file (not compile-won))
1549         (setq output-file-name (pathname (fasl-file-stream fasl-file)))
1550         (when (and compile-won sb!xc:*compile-verbose*)
1551           ;; MNA: compiler message patch
1552           (compiler-mumble "~2&; ~A written~%" (namestring output-file-name))))
1553
1554       (when sb!xc:*compile-verbose*
1555         (finish-error-output source-info compile-won)))
1556
1557     (values (if output-file
1558                 ;; Hack around filesystem race condition...
1559                 (or (probe-file output-file-name) output-file-name)
1560                 nil)
1561             warnings-p
1562             failure-p)))
1563 \f
1564 (defun sb!xc:compile-file-pathname (file-path
1565                                     &key (output-file t) byte-compile
1566                                     &allow-other-keys)
1567   #!+sb-doc
1568   "Return a pathname describing what file COMPILE-FILE would write to given
1569    these arguments."
1570   (declare (values (or null pathname)))
1571   (let ((pathname (pathname file-path)))
1572     (cond ((not (eq output-file t))
1573            (when output-file
1574              (translate-logical-pathname (pathname output-file))))
1575           ((and (typep pathname 'logical-pathname) (not (eq byte-compile t)))
1576            (make-pathname :type "FASL" :defaults pathname
1577                           :case :common))
1578           (t
1579            (make-pathname :defaults (translate-logical-pathname pathname)
1580                           :type (if (eq byte-compile t)
1581                                     (backend-byte-fasl-file-type)
1582                                     *backend-fasl-file-type*))))))