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