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