X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=src%2Fcompiler%2Fmain.lisp;h=a99e5ba0034a12b8bc0b6e98d2b5fde2b267090b;hb=cf607a404d7518e8a18c9e362913f370eb9a5e38;hp=f3b81da7016e48ab006985466bc609d144e43143;hpb=20748f2dd7965dcd1446a1cb27e5a5af18a0e5bb;p=sbcl.git diff --git a/src/compiler/main.lisp b/src/compiler/main.lisp index f3b81da..a99e5ba 100644 --- a/src/compiler/main.lisp +++ b/src/compiler/main.lisp @@ -14,10 +14,10 @@ (in-package "SB!C") ;;; FIXME: Doesn't this belong somewhere else, like early-c.lisp? -(declaim (special *constants* *free-variables* *component-being-compiled* +(declaim (special *constants* *free-vars* *component-being-compiled* *code-vector* *next-location* *result-fixups* - *free-functions* *source-paths* - *seen-blocks* *seen-functions* *list-conflicts-table* + *free-funs* *source-paths* + *seen-blocks* *seen-funs* *list-conflicts-table* *continuation-number* *continuation-numbers* *number-continuations* *tn-id* *tn-ids* *id-tns* *label-ids* *label-id* *id-labels* @@ -40,13 +40,11 @@ ;;; :BLOCK-COMPILE and :ENTRY-POINTS arguments that COMPILE-FILE was ;;; called with. ;;; -;;; *BLOCK-COMPILE-ARGUMENT* holds the original value of the -;;; :BLOCK-COMPILE argument, which overrides any internal -;;; declarations. +;;; *BLOCK-COMPILE-ARG* holds the original value of the :BLOCK-COMPILE +;;; argument, which overrides any internal declarations. (defvar *block-compile*) -(defvar *block-compile-argument*) -(declaim (type (member nil t :specified) - *block-compile* *block-compile-argument*)) +(defvar *block-compile-arg*) +(declaim (type (member nil t :specified) *block-compile* *block-compile-arg*)) (defvar *entry-points*) (declaim (list *entry-points*)) @@ -163,23 +161,23 @@ (warning #'compiler-warning-handler)) (let ((undefs (sort *undefined-warnings* #'string< - :key #'(lambda (x) - (let ((x (undefined-warning-name x))) - (if (symbolp x) - (symbol-name x) - (prin1-to-string x))))))) + :key (lambda (x) + (let ((x (undefined-warning-name x))) + (if (symbolp x) + (symbol-name x) + (prin1-to-string x))))))) (dolist (undef undefs) (let ((name (undefined-warning-name undef)) (kind (undefined-warning-kind undef)) (warnings (undefined-warning-warnings undef)) (undefined-warning-count (undefined-warning-count undef))) (dolist (*compiler-error-context* warnings) - (compiler-style-warning "undefined ~(~A~): ~S" kind name)) + (compiler-style-warn "undefined ~(~A~): ~S" kind name)) (let ((warn-count (length warnings))) (when (and warnings (> undefined-warning-count warn-count)) (let ((more (- undefined-warning-count warn-count))) - (compiler-style-warning - "~D more use~:P of undefined ~(~A~) ~S" + (compiler-style-warn + "~W more use~:P of undefined ~(~A~) ~S" more kind name)))))) (dolist (kind '(:variable :function :type)) @@ -187,7 +185,7 @@ (remove kind undefs :test-not #'eq :key #'undefined-warning-kind)))) (when summary - (compiler-style-warning + (compiler-style-warn "~:[This ~(~A~) is~;These ~(~A~)s are~] undefined:~ ~% ~{~<~% ~1:;~S~>~^ ~}" (cdr summary) kind summary))))))) @@ -201,11 +199,11 @@ (format *error-output* "~&") (pprint-logical-block (*error-output* nil :per-line-prefix "; ") (compiler-mumble "compilation unit ~:[finished~;aborted~]~ - ~[~:;~:*~& caught ~D fatal ERROR condition~:P~]~ - ~[~:;~:*~& caught ~D ERROR condition~:P~]~ - ~[~:;~:*~& caught ~D WARNING condition~:P~]~ - ~[~:;~:*~& caught ~D STYLE-WARNING condition~:P~]~ - ~[~:;~:*~& printed ~D note~:P~]" + ~[~:;~:*~& caught ~W fatal ERROR condition~:P~]~ + ~[~:;~:*~& caught ~W ERROR condition~:P~]~ + ~[~:;~:*~& caught ~W WARNING condition~:P~]~ + ~[~:;~:*~& caught ~W STYLE-WARNING condition~:P~]~ + ~[~:;~:*~& printed ~W note~:P~]" abort-p *aborted-compilation-unit-count* *compiler-error-count* @@ -310,14 +308,15 @@ ;;; Do all the IR1 phases for a non-top-level component. (defun ir1-phases (component) (declare (type component component)) + (aver-live-component component) (let ((*constraint-number* 0) (loop-count 1) (*delayed-ir1-transforms* nil)) (declare (special *constraint-number* *delayed-ir1-transforms*)) (loop (ir1-optimize-until-done component) - (when (or (component-new-funs component) - (component-reanalyze-funs component)) + (when (or (component-new-functionals component) + (component-reanalyze-functionals component)) (maybe-mumble "locall ") (locall-analyze-component component)) (dfo-as-needed component) @@ -326,21 +325,20 @@ (constraint-propagate component)) (when (retry-delayed-ir1-transforms :constraint) (maybe-mumble "Rtran ")) - ;; Delay the generation of type checks until the type - ;; constraints have had time to propagate, else the compiler can - ;; confuse itself. - (unless (and (or (component-reoptimize component) - (component-reanalyze component) - (component-new-funs component) - (component-reanalyze-funs component)) - (< loop-count (- *reoptimize-after-type-check-max* 4))) - (maybe-mumble "type ") - (generate-type-checks component) - (unless (or (component-reoptimize component) - (component-reanalyze component) - (component-new-funs component) - (component-reanalyze-funs component)) - (return))) + (flet ((want-reoptimization-p () + (or (component-reoptimize component) + (component-reanalyze component) + (component-new-functionals component) + (component-reanalyze-functionals component)))) + (unless (and (want-reoptimization-p) + ;; We delay the generation of type checks until + ;; the type constraints have had time to + ;; propagate, else the compiler can confuse itself. + (< loop-count (- *reoptimize-after-type-check-max* 4))) + (maybe-mumble "type ") + (generate-type-checks component) + (unless (want-reoptimization-p) + (return)))) (when (>= loop-count *reoptimize-after-type-check-max*) (maybe-mumble "[reoptimize limit]") (event reoptimize-maxed-out) @@ -440,7 +438,7 @@ (null)))))) ;; We're done, so don't bother keeping anything around. - (setf (component-info component) nil) + (setf (component-info component) :dead) (values)) @@ -456,12 +454,27 @@ (:toplevel (return)) (:external (unless (every (lambda (ref) - (eq (block-component (node-block ref)) - component)) + (eq (node-component ref) component)) (leaf-refs fun)) (return)))))) (defun compile-component (component) + + ;; miscellaneous sanity checks + ;; + ;; FIXME: These are basically pretty wimpy compared to the checks done + ;; by the old CHECK-IR1-CONSISTENCY code. It would be really nice to + ;; make those internal consistency checks work again and use them. + (aver-live-component component) + (do-blocks (block component) + (aver (eql (block-component block) component))) + (dolist (lambda (component-lambdas component)) + ;; sanity check to prevent weirdness from propagating insidiously as + ;; far from its root cause as it did in bug 138: Make sure that + ;; thing-to-COMPONENT links are consistent. + (aver (eql (lambda-component lambda) component)) + (aver (eql (node-component (lambda-bind lambda)) component))) + (let* ((*component-being-compiled* component)) (when sb!xc:*compile-print* (compiler-mumble "~&; compiling ~A: " (component-name component))) @@ -492,22 +505,22 @@ ;;;; global data structures entirely when possible and consing up the ;;;; others from scratch instead of clearing and reusing them? -;;; Clear the INFO in constants in the *FREE-VARIABLES*, etc. In +;;; Clear the INFO in constants in the *FREE-VARS*, etc. In ;;; addition to allowing stuff to be reclaimed, this is required for ;;; correct assignment of constant offsets, since we need to assign a ;;; new offset for each component. We don't clear the FUNCTIONAL-INFO ;;; slots, since they are used to keep track of functions across ;;; component boundaries. (defun clear-constant-info () - (maphash #'(lambda (k v) - (declare (ignore k)) - (setf (leaf-info v) nil)) + (maphash (lambda (k v) + (declare (ignore k)) + (setf (leaf-info v) nil)) *constants*) - (maphash #'(lambda (k v) - (declare (ignore k)) - (when (constant-p v) - (setf (leaf-info v) nil))) - *free-variables*) + (maphash (lambda (k v) + (declare (ignore k)) + (when (constant-p v) + (setf (leaf-info v) nil))) + *free-vars*) (values)) ;;; Blow away the REFS for all global variables, and let COMPONENT @@ -515,19 +528,19 @@ (defun clear-ir1-info (component) (declare (type component component)) (labels ((blast (x) - (maphash #'(lambda (k v) - (declare (ignore k)) - (when (leaf-p v) - (setf (leaf-refs v) - (delete-if #'here-p (leaf-refs v))) - (when (basic-var-p v) - (setf (basic-var-sets v) - (delete-if #'here-p (basic-var-sets v)))))) + (maphash (lambda (k v) + (declare (ignore k)) + (when (leaf-p v) + (setf (leaf-refs v) + (delete-if #'here-p (leaf-refs v))) + (when (basic-var-p v) + (setf (basic-var-sets v) + (delete-if #'here-p (basic-var-sets v)))))) x)) (here-p (x) - (eq (block-component (node-block x)) component))) - (blast *free-variables*) - (blast *free-functions*) + (eq (node-component x) component))) + (blast *free-vars*) + (blast *free-funs*) (blast *constants*)) (values)) @@ -540,14 +553,14 @@ (defun clear-stuff (&optional (debug-too t)) ;; Clear global tables. - (when (boundp '*free-functions*) - (clrhash *free-functions*) - (clrhash *free-variables*) + (when (boundp '*free-funs*) + (clrhash *free-funs*) + (clrhash *free-vars*) (clrhash *constants*)) ;; Clear debug counters and tables. (clrhash *seen-blocks*) - (clrhash *seen-functions*) + (clrhash *seen-funs*) (clrhash *list-conflicts-table*) (when debug-too @@ -580,7 +593,7 @@ ;;;; trace output -;;; Print out some useful info about Component to Stream. +;;; Print out some useful info about COMPONENT to STREAM. (defun describe-component (component *standard-output*) (declare (type component component)) (format t "~|~%;;;; component: ~S~2%" (component-name component)) @@ -609,7 +622,7 @@ ;;;; the error context and for recovering from errors. ;;;; ;;;; The interface we provide to this stuff is the stream-oid -;;;; Source-Info structure. The bookkeeping is done as a side-effect +;;;; SOURCE-INFO structure. The bookkeeping is done as a side effect ;;;; of getting the next source form. ;;; A FILE-INFO structure holds all the source information for a @@ -786,11 +799,11 @@ ;;; Process a top level use of LOCALLY, or anything else (e.g. ;;; MACROLET) at top level which has declarations and ordinary forms. ;;; We parse declarations and then recursively process the body. -(defun process-toplevel-locally (body path compile-time-too) +(defun process-toplevel-locally (body path compile-time-too &key vars funs) (declare (list path)) - (multiple-value-bind (forms decls) (sb!sys:parse-body body nil) + (multiple-value-bind (forms decls) (parse-body body nil) (let* ((*lexenv* - (process-decls decls nil nil (make-continuation))) + (process-decls decls vars funs (make-continuation))) ;; Binding *POLICY* is pretty much of a hack, since it ;; causes LOCALLY to "capture" enclosed proclamations. It ;; is necessary because CONVERT-AND-MAYBE-COMPILE uses the @@ -857,17 +870,16 @@ (setf (component-name component) (debug-namify "~S initial component" name)) (setf (component-kind component) :initial) - (let* ((locall-fun (ir1-convert-lambda definition - :debug-name (debug-namify - "top level locall ~S" - name))) + (let* ((locall-fun (ir1-convert-lambda + definition + :debug-name (debug-namify "top level local call ~S" + name))) (fun (ir1-convert-lambda (make-xep-lambda-expression locall-fun) :source-name (or name '.anonymous.) :debug-name (unless name "top level form")))) - (/show "in MAKE-FUNCTIONAL-FROM-TOP-LEVEL-LAMBDA" locall-fun fun component) - (/show (component-lambdas component)) - (/show (lambda-calls fun)) + (when name + (assert-global-function-definition-type name locall-fun)) (setf (functional-entry-fun fun) locall-fun (functional-kind fun) :external (functional-has-external-references-p fun) t) @@ -893,15 +905,12 @@ ;; nice default for things where we don't have a ;; real source path (as in e.g. inside CL:COMPILE). '(original-source-start 0 0))) - (/show "entering %COMPILE" lambda-expression name) - (unless (or (null name) (legal-fun-name-p name)) - (error "not a legal function name: ~S" name)) + (when name + (legal-fun-name-or-type-error name)) (let* ((*lexenv* (make-lexenv :policy *policy*)) (fun (make-functional-from-toplevel-lambda lambda-expression :name name :path path))) - (/show "back in %COMPILE from M-F-FROM-TL-LAMBDA" fun) - (/show (lambda-component fun) (component-lambdas (lambda-component fun))) ;; FIXME: The compile-it code from here on is sort of a ;; twisted version of the code in COMPILE-TOPLEVEL. It'd be @@ -911,17 +920,10 @@ ;; the :LOCALL-ONLY option to IR1-FOR-LAMBDA. Then maybe the ;; whole FUNCTIONAL-KIND=:TOPLEVEL case could go away..) - #+nil (break "before LOCALL-ANALYZE-CLAMBDAS-UNTIL-DONE" fun) (locall-analyze-clambdas-until-done (list fun)) - (/show (lambda-calls fun)) - #+nil (break "back from LOCALL-ANALYZE-CLAMBDAS-UNTIL-DONE" fun) (multiple-value-bind (components-from-dfo top-components hairy-top) (find-initial-dfo (list fun)) - (/show components-from-dfo top-components hairy-top) - (/show (mapcar #'component-lambdas components-from-dfo)) - (/show (mapcar #'component-lambdas top-components)) - (/show (mapcar #'component-lambdas hairy-top)) (let ((*all-components* (append components-from-dfo top-components))) ;; FIXME: This is more monkey see monkey do based on CMU CL @@ -932,7 +934,6 @@ (mapc #'preallocate-physenvs-for-toplevelish-lambdas hairy-top) (mapc #'preallocate-physenvs-for-toplevelish-lambdas top-components) (dolist (component-from-dfo components-from-dfo) - (/show component-from-dfo (component-lambdas component-from-dfo)) (compile-component component-from-dfo) (replace-toplevel-xeps component-from-dfo))) @@ -946,15 +947,36 @@ (gethash (leaf-info fun) entry-table) (aver found-p) result)) + ;; KLUDGE: This code duplicates some other code in this + ;; file. In the great reorganzation, the flow of program logic + ;; changed from the original CMUCL model, and that path (as of + ;; sbcl-0.7.5 in SUB-COMPILE-FILE) was no longer followed for + ;; CORE-OBJECTS, leading to BUG 156. This place is + ;; transparently not the right one for this code, but I don't + ;; have a clear enough overview of the compiler to know how to + ;; rearrange it all so that this operation fits in nicely, and + ;; it was blocking reimplementation of + ;; (DECLAIM (INLINE FOO)) (MACROLET ((..)) (DEFUN FOO ...)) + ;; + ;; FIXME: This KLUDGE doesn't solve all the problem in an + ;; ideal way, as (1) definitions typed in at the REPL without + ;; an INLINE declaration will give a NULL + ;; FUNCTION-LAMBDA-EXPRESSION (allowable, but not ideal) and + ;; (2) INLINE declarations will yield a + ;; FUNCTION-LAMBDA-EXPRESSION headed by + ;; SB-C:LAMBDA-WITH-LEXENV, even for null LEXENV. + ;; + ;; CSR, 2002-07-02 + (when (core-object-p *compile-object*) + (fix-core-source-info *source-info* *compile-object*)) + (mapc #'clear-ir1-info components-from-dfo) - (clear-stuff) - (/show "returning from %COMPILE"))))) + (clear-stuff))))) (defun process-toplevel-cold-fset (name lambda-expression path) (unless (producing-fasl-file) (error "can't COLD-FSET except in a fasl file")) - (unless (legal-fun-name-p name) - (error "not a legal function name: ~S" name)) + (legal-fun-name-or-type-error name) (fasl-dump-cold-fset name (%compile lambda-expression *compile-object* @@ -979,130 +1001,140 @@ (*compiler-error-bailout* (lambda () (convert-and-maybe-compile - `(error "execution of a form compiled with errors:~% ~S" - ',form) + `(error 'simple-program-error + :format-control "execution of a form compiled with errors:~% ~S" + :format-arguments (list ',form)) path) (throw 'process-toplevel-form-error-abort nil)))) - (if (atom form) - ;; (There are no EVAL-WHEN issues in the ATOM case until - ;; SBCL gets smart enough to handle global - ;; DEFINE-SYMBOL-MACRO.) - (convert-and-maybe-compile form path) - (flet ((need-at-least-one-arg (form) - (unless (cdr form) - (compiler-error "~S form is too short: ~S" - (car form) - form)))) - (case (car form) - ;; In the cross-compiler, top level COLD-FSET arranges - ;; for static linking at cold init time. - #+sb-xc-host - ((cold-fset) - (aver (not compile-time-too)) - (destructuring-bind (cold-fset fun-name lambda-expression) form - (declare (ignore cold-fset)) - (process-toplevel-cold-fset fun-name - lambda-expression - path))) - ((eval-when macrolet symbol-macrolet);things w/ 1 arg before body - (need-at-least-one-arg form) - (destructuring-bind (special-operator magic &rest body) form - (ecase special-operator - ((eval-when) - ;; CT, LT, and E here are as in Figure 3-7 of ANSI - ;; "3.2.3.1 Processing of Top Level Forms". - (multiple-value-bind (ct lt e) - (parse-eval-when-situations magic) - (let ((new-compile-time-too (or ct - (and compile-time-too - e)))) - (cond (lt (process-toplevel-progn - body path new-compile-time-too)) - (new-compile-time-too (eval - `(progn ,@body))))))) - ((macrolet) - (funcall-in-macrolet-lexenv - magic - (lambda () - (process-toplevel-locally body - path - compile-time-too)))) - ((symbol-macrolet) - (funcall-in-symbol-macrolet-lexenv - magic - (lambda () - (process-toplevel-locally body - path - compile-time-too))))))) - ((locally) - (process-toplevel-locally (rest form) path compile-time-too)) - ((progn) - (process-toplevel-progn (rest form) path compile-time-too)) - ;; When we're cross-compiling, consider: what should we - ;; do when we hit e.g. - ;; (EVAL-WHEN (:COMPILE-TOPLEVEL) - ;; (DEFUN FOO (X) (+ 7 X)))? - ;; DEFUN has a macro definition in the cross-compiler, - ;; and a different macro definition in the target - ;; compiler. The only sensible thing is to use the - ;; target compiler's macro definition, since the - ;; cross-compiler's macro is in general into target - ;; functions which can't meaningfully be executed at - ;; cross-compilation time. So make sure we do the EVAL - ;; here, before we macroexpand. - ;; - ;; Then things get even dicier with something like - ;; (DEFCONSTANT-EQX SB!XC:LAMBDA-LIST-KEYWORDS ..) - ;; where we have to make sure that we don't uncross - ;; the SB!XC: prefix before we do EVAL, because otherwise - ;; we'd be trying to redefine the cross-compilation host's - ;; constants. - ;; - ;; (Isn't it fun to cross-compile Common Lisp?:-) - #+sb-xc-host - (t - (when compile-time-too - (eval form)) ; letting xc host EVAL do its own macroexpansion - (let* (;; (We uncross the operator name because things - ;; like SB!XC:DEFCONSTANT and SB!XC:DEFTYPE - ;; should be equivalent to their CL: counterparts - ;; when being compiled as target code. We leave - ;; the rest of the form uncrossed because macros - ;; might yet expand into EVAL-WHEN stuff, and - ;; things inside EVAL-WHEN can't be uncrossed - ;; until after we've EVALed them in the - ;; cross-compilation host.) - (slightly-uncrossed (cons (uncross (first form)) - (rest form))) - (expanded (preprocessor-macroexpand-1 - slightly-uncrossed))) - (if (eq expanded slightly-uncrossed) - ;; (Now that we're no longer processing toplevel - ;; forms, and hence no longer need to worry about - ;; EVAL-WHEN, we can uncross everything.) - (convert-and-maybe-compile expanded path) - ;; (We have to demote COMPILE-TIME-TOO to NIL - ;; here, no matter what it was before, since - ;; otherwise we'd tend to EVAL subforms more than - ;; once, because of WHEN COMPILE-TIME-TOO form - ;; above.) - (process-toplevel-form expanded path nil)))) - ;; When we're not cross-compiling, we only need to - ;; macroexpand once, so we can follow the 1-thru-6 - ;; sequence of steps in ANSI's "3.2.3.1 Processing of - ;; Top Level Forms". - #-sb-xc-host - (t - (let ((expanded (preprocessor-macroexpand-1 form))) + (flet ((default-processor (form) + ;; When we're cross-compiling, consider: what should we + ;; do when we hit e.g. + ;; (EVAL-WHEN (:COMPILE-TOPLEVEL) + ;; (DEFUN FOO (X) (+ 7 X)))? + ;; DEFUN has a macro definition in the cross-compiler, + ;; and a different macro definition in the target + ;; compiler. The only sensible thing is to use the + ;; target compiler's macro definition, since the + ;; cross-compiler's macro is in general into target + ;; functions which can't meaningfully be executed at + ;; cross-compilation time. So make sure we do the EVAL + ;; here, before we macroexpand. + ;; + ;; Then things get even dicier with something like + ;; (DEFCONSTANT-EQX SB!XC:LAMBDA-LIST-KEYWORDS ..) + ;; where we have to make sure that we don't uncross + ;; the SB!XC: prefix before we do EVAL, because otherwise + ;; we'd be trying to redefine the cross-compilation host's + ;; constants. + ;; + ;; (Isn't it fun to cross-compile Common Lisp?:-) + #+sb-xc-host + (progn + (when compile-time-too + (eval form)) ; letting xc host EVAL do its own macroexpansion + (let* (;; (We uncross the operator name because things + ;; like SB!XC:DEFCONSTANT and SB!XC:DEFTYPE + ;; should be equivalent to their CL: counterparts + ;; when being compiled as target code. We leave + ;; the rest of the form uncrossed because macros + ;; might yet expand into EVAL-WHEN stuff, and + ;; things inside EVAL-WHEN can't be uncrossed + ;; until after we've EVALed them in the + ;; cross-compilation host.) + (slightly-uncrossed (cons (uncross (first form)) + (rest form))) + (expanded (preprocessor-macroexpand-1 + slightly-uncrossed))) + (if (eq expanded slightly-uncrossed) + ;; (Now that we're no longer processing toplevel + ;; forms, and hence no longer need to worry about + ;; EVAL-WHEN, we can uncross everything.) + (convert-and-maybe-compile expanded path) + ;; (We have to demote COMPILE-TIME-TOO to NIL + ;; here, no matter what it was before, since + ;; otherwise we'd tend to EVAL subforms more than + ;; once, because of WHEN COMPILE-TIME-TOO form + ;; above.) + (process-toplevel-form expanded path nil)))) + ;; When we're not cross-compiling, we only need to + ;; macroexpand once, so we can follow the 1-thru-6 + ;; sequence of steps in ANSI's "3.2.3.1 Processing of + ;; Top Level Forms". + #-sb-xc-host + (let ((expanded (preprocessor-macroexpand-1 form))) (cond ((eq expanded form) (when compile-time-too - (eval form)) + (eval-in-lexenv form *lexenv*)) (convert-and-maybe-compile form path)) (t (process-toplevel-form expanded path - compile-time-too)))))))))) + compile-time-too)))))) + (if (atom form) + #+sb-xc-host + ;; (There are no xc EVAL-WHEN issues in the ATOM case until + ;; (1) SBCL gets smart enough to handle global + ;; DEFINE-SYMBOL-MACRO or SYMBOL-MACROLET and (2) SBCL + ;; implementors start using symbol macros in a way which + ;; interacts with SB-XC/CL distinction.) + (convert-and-maybe-compile form path) + #-sb-xc-host + (default-processor form) + (flet ((need-at-least-one-arg (form) + (unless (cdr form) + (compiler-error "~S form is too short: ~S" + (car form) + form)))) + (case (car form) + ;; In the cross-compiler, top level COLD-FSET arranges + ;; for static linking at cold init time. + #+sb-xc-host + ((cold-fset) + (aver (not compile-time-too)) + (destructuring-bind (cold-fset fun-name lambda-expression) form + (declare (ignore cold-fset)) + (process-toplevel-cold-fset fun-name + lambda-expression + path))) + ((eval-when macrolet symbol-macrolet);things w/ 1 arg before body + (need-at-least-one-arg form) + (destructuring-bind (special-operator magic &rest body) form + (ecase special-operator + ((eval-when) + ;; CT, LT, and E here are as in Figure 3-7 of ANSI + ;; "3.2.3.1 Processing of Top Level Forms". + (multiple-value-bind (ct lt e) + (parse-eval-when-situations magic) + (let ((new-compile-time-too (or ct + (and compile-time-too + e)))) + (cond (lt (process-toplevel-progn + body path new-compile-time-too)) + (new-compile-time-too (eval-in-lexenv + `(progn ,@body) + *lexenv*)))))) + ((macrolet) + (funcall-in-macrolet-lexenv + magic + (lambda (&key funs) + (declare (ignore funs)) + (process-toplevel-locally body + path + compile-time-too)))) + ((symbol-macrolet) + (funcall-in-symbol-macrolet-lexenv + magic + (lambda (&key vars) + (process-toplevel-locally body + path + compile-time-too + :vars vars))))))) + ((locally) + (process-toplevel-locally (rest form) path compile-time-too)) + ((progn) + (process-toplevel-progn (rest form) path compile-time-too)) + (t (default-processor form)))))))) (values)) @@ -1117,15 +1149,8 @@ ;;; Compile FORM and arrange for it to be called at load-time. Return ;;; the dumper handle and our best guess at the type of the object. -(defun compile-load-time-value - (form &optional - (name (let ((*print-level* 2) (*print-length* 3)) - (format nil "load time value of ~S" - (if (and (listp form) - (eq (car form) 'make-value-cell)) - (second form) - form))))) - (let ((lambda (compile-load-time-stuff form name t))) +(defun compile-load-time-value (form) + (let ((lambda (compile-load-time-stuff form t))) (values (fasl-dump-load-time-value-lambda lambda *compile-object*) (let ((type (leaf-type lambda))) @@ -1135,13 +1160,13 @@ ;;; Compile the FORMS and arrange for them to be called (for effect, ;;; not value) at load time. -(defun compile-make-load-form-init-forms (forms name) - (let ((lambda (compile-load-time-stuff `(progn ,@forms) name nil))) +(defun compile-make-load-form-init-forms (forms) + (let ((lambda (compile-load-time-stuff `(progn ,@forms) nil))) (fasl-dump-toplevel-lambda-call lambda *compile-object*))) -;;; Does the actual work of COMPILE-LOAD-TIME-VALUE or -;;; COMPILE-MAKE-LOAD-FORM- INIT-FORMS. -(defun compile-load-time-stuff (form name for-value) +;;; Do the actual work of COMPILE-LOAD-TIME-VALUE or +;;; COMPILE-MAKE-LOAD-FORM-INIT-FORMS. +(defun compile-load-time-stuff (form for-value) (with-ir1-namespace (let* ((*lexenv* (make-null-lexenv)) (lambda (ir1-toplevel form *current-path* for-value))) @@ -1164,87 +1189,47 @@ ;;;; COMPILE-FILE -;;; We build a list of top level lambdas, and then periodically smash -;;; them together into a single component and compile it. -(defvar *pending-toplevel-lambdas*) - -;;; The maximum number of top level lambdas we put in a single -;;; top level component. -;;; -;;; CMU CL 18b used this nontrivially by default (setting it to 10) -;;; but consequently suffered from the inability to execute some -;;; troublesome constructs correctly, e.g. inability to load a fasl -;;; file compiled from the source file -;;; (defpackage "FOO" (:use "CL")) -;;; (print 'foo::bar) -;;; because it would dump data-setup fops (including a FOP-PACKAGE for -;;; "FOO") for the second form before dumping the the code in the -;;; first form, or the fop to execute the code in the first form. By -;;; setting this value to 0 by default, we avoid this badness. This -;;; increases the number of toplevel form functions, and so increases -;;; the size of object files. -;;; -;;; The variable is still supported because when we are compiling the -;;; SBCL system itself, which is known not contain any troublesome -;;; constructs, we can set it to a nonzero value, which reduces the -;;; number of toplevel form objects, reducing the peak memory usage in -;;; GENESIS, which is desirable, since at least for SBCL version -;;; 0.6.7, this is the high water mark for memory usage during system -;;; construction. -(defparameter *toplevel-lambda-max* 0) - (defun object-call-toplevel-lambda (tll) (declare (type functional tll)) (let ((object *compile-object*)) (etypecase object - (fasl-output - (fasl-dump-toplevel-lambda-call tll object)) - (core-object - (core-call-toplevel-lambda tll object)) + (fasl-output (fasl-dump-toplevel-lambda-call tll object)) + (core-object (core-call-toplevel-lambda tll object)) (null)))) -;;; Add LAMBDAS to the pending lambdas. If this leaves more than -;;; *TOPLEVEL-LAMBDA-MAX* lambdas in the list, or if FORCE-P is true, -;;; then smash the lambdas into a single component, compile it, and -;;; call the resulting function. -(defun sub-compile-toplevel-lambdas (lambdas force-p) +;;; Smash LAMBDAS into a single component, compile it, and arrange for +;;; the resulting function to be called. +(defun sub-compile-toplevel-lambdas (lambdas) (declare (list lambdas)) - (setq *pending-toplevel-lambdas* - (append *pending-toplevel-lambdas* lambdas)) - (let ((pending *pending-toplevel-lambdas*)) - (when (and pending - (or (> (length pending) *toplevel-lambda-max*) - force-p)) - (multiple-value-bind (component tll) (merge-toplevel-lambdas pending) - (setq *pending-toplevel-lambdas* ()) - (compile-component component) - (clear-ir1-info component) - (object-call-toplevel-lambda tll)))) + (when lambdas + (multiple-value-bind (component tll) (merge-toplevel-lambdas lambdas) + (compile-component component) + (clear-ir1-info component) + (object-call-toplevel-lambda tll))) (values)) ;;; Compile top level code and call the top level lambdas. We pick off ;;; top level lambdas in non-top-level components here, calling ;;; SUB-c-t-l-l on each subsequence of normal top level lambdas. -(defun compile-toplevel-lambdas (lambdas force-p) +(defun compile-toplevel-lambdas (lambdas) (declare (list lambdas)) (let ((len (length lambdas))) (flet ((loser (start) (or (position-if (lambda (x) (not (eq (component-kind - (block-component - (node-block - (lambda-bind x)))) + (node-component (lambda-bind x))) :toplevel))) lambdas - :start start) + ;; this used to read ":start start", but + ;; start can be greater than len, which + ;; is an error according to ANSI - CSR, + ;; 2002-04-25 + :start (min start len)) len))) (do* ((start 0 (1+ loser)) (loser (loser start) (loser start))) - ((>= start len) - (when force-p - (sub-compile-toplevel-lambdas nil t))) - (sub-compile-toplevel-lambdas (subseq lambdas start loser) - (or force-p (/= loser len))) + ((>= start len)) + (sub-compile-toplevel-lambdas (subseq lambdas start loser)) (unless (= loser len) (object-call-toplevel-lambda (elt lambdas loser)))))) (values)) @@ -1263,20 +1248,17 @@ (maybe-mumble "IDFO ") (multiple-value-bind (components top-components hairy-top) (find-initial-dfo lambdas) - (let ((*all-components* (append components top-components)) - (toplevel-closure nil)) + (let ((*all-components* (append components top-components))) (when *check-consistency* (maybe-mumble "[check]~%") (check-ir1-consistency *all-components*)) (dolist (component (append hairy-top top-components)) - (when (pre-physenv-analyze-toplevel component) - (setq toplevel-closure t))) + (pre-physenv-analyze-toplevel component)) (dolist (component components) (compile-component component) - (when (replace-toplevel-xeps component) - (setq toplevel-closure t))) + (replace-toplevel-xeps component)) (when *check-consistency* (maybe-mumble "[check]~%") @@ -1284,7 +1266,7 @@ (if load-time-value-p (compile-load-time-value-lambda lambdas) - (compile-toplevel-lambdas lambdas toplevel-closure)) + (compile-toplevel-lambdas lambdas)) (mapc #'clear-ir1-info components) (clear-stuff))) @@ -1304,7 +1286,7 @@ ;;; Return (VALUES NIL WARNINGS-P FAILURE-P). (defun sub-compile-file (info) (declare (type source-info info)) - (let* ((*block-compile* *block-compile-argument*) + (let* ((*block-compile* *block-compile-arg*) (*package* (sane-package)) (*policy* *policy*) (*lexenv* (make-null-lexenv)) @@ -1312,7 +1294,6 @@ (sb!xc:*compile-file-pathname* nil) (sb!xc:*compile-file-truename* nil) (*toplevel-lambdas* ()) - (*pending-toplevel-lambdas* ()) (*compiler-error-bailout* (lambda () (compiler-mumble "~2&; fatal error, aborting compilation~%") @@ -1339,7 +1320,6 @@ (sub-sub-compile-file info) (finish-block-compilation) - (compile-toplevel-lambdas () t) (let ((object *compile-object*)) (etypecase object (fasl-output (fasl-dump-source-info info object)) @@ -1417,7 +1397,7 @@ ;; extensions (trace-file nil) - ((:block-compile *block-compile-argument*) nil)) + ((:block-compile *block-compile-arg*) nil)) #!+sb-doc "Compile INPUT-FILE, producing a corresponding fasl file and returning @@ -1534,7 +1514,7 @@ #!+sb-doc "Return a pathname describing what file COMPILE-FILE would write to given these arguments." - (pathname output-file)) + (merge-pathnames output-file (merge-pathnames input-file))) ;;;; MAKE-LOAD-FORM stuff @@ -1569,7 +1549,7 @@ ;;; If the constant doesn't show up in *CONSTANTS-BEING-CREATED*, then ;;; we have to create it. We call MAKE-LOAD-FORM and check to see ;;; whether the creation form is the magic value -;;; :JUST-DUMP-IT-NORMALLY. If it is, then we don't do anything. The +;;; :SB-JUST-DUMP-IT-NORMALLY. If it is, then we don't do anything. The ;;; dumper will eventually get its hands on the object and use the ;;; normal structure dumping noise on it. ;;; @@ -1586,7 +1566,7 @@ ;;; deal with it. (defvar *constants-being-created* nil) (defvar *constants-created-since-last-init* nil) -;;; FIXME: Shouldn't these^ variables be bound in LET forms? +;;; FIXME: Shouldn't these^ variables be unbound outside LET forms? (defun emit-make-load-form (constant) (aver (fasl-output-p *compile-object*)) (unless (or (fasl-constant-already-dumped-p constant *compile-object*) @@ -1610,13 +1590,12 @@ constant condition))) (case creation-form - (:just-dump-it-normally + (:sb-just-dump-it-normally (fasl-validate-structure constant *compile-object*) t) (:ignore-it nil) (t - (compile-toplevel-lambdas () t) (when (fasl-constant-already-dumped-p constant *compile-object*) (return-from emit-make-load-form nil)) (let* ((name (let ((*print-level* 1) (*print-length* 2)) @@ -1634,8 +1613,7 @@ (fasl-note-handle-for-constant constant (compile-load-time-value - creation-form - (format nil "creation form for ~A" name)) + creation-form) *compile-object*) nil) (compiler-error "circular references in creation form for ~S" @@ -1647,12 +1625,20 @@ (loop for (name form) on (cdr info) by #'cddr collect name into names collect form into forms - finally - (compile-make-load-form-init-forms - forms - (format nil "init form~:[~;s~] for ~{~A~^, ~}" - (cdr forms) names))) + finally (compile-make-load-form-init-forms forms)) nil))) (when circular-ref (setf (cdr circular-ref) (append (cdr circular-ref) (cdr info)))))))))))) + + +;;;; Host compile time definitions +#+sb-xc-host +(defun compile-in-lexenv (name lambda lexenv) + (declare (ignore lexenv)) + (compile name lambda)) + +#+sb-xc-host +(defun eval-in-lexenv (form lexenv) + (declare (ignore lexenv)) + (eval form))