1 ;;;; miscellaneous types and macros used in writing the compiler
3 ;;;; This software is part of the SBCL system. See the README file for
6 ;;;; This software is derived from the CMU CL system, which was
7 ;;;; written at Carnegie Mellon University and released into the
8 ;;;; public domain. The software is in the public domain and is
9 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
10 ;;;; files for more information.
14 (declaim (special *wild-type* *universal-type* *compiler-error-context*))
16 ;;; An INLINEP value describes how a function is called. The values
17 ;;; have these meanings:
18 ;;; NIL No declaration seen: do whatever you feel like, but don't
19 ;;; dump an inline expansion.
20 ;;; :NOTINLINE NOTINLINE declaration seen: always do full function call.
21 ;;; :INLINE INLINE declaration seen: save expansion, expanding to it
24 ;;; Retain expansion, but only use it opportunistically.
25 ;;; :MAYBE-INLINE is quite different from :INLINE. As explained
26 ;;; by APD on #lisp 2005-11-26: "MAYBE-INLINE lambda is
27 ;;; instantiated once per component, INLINE - for all
28 ;;; references (even under #'without FUNCALL)."
29 (deftype inlinep () '(member :inline :maybe-inline :notinline nil))
31 ;;;; source-hacking defining forms
33 ;;; Parse a DEFMACRO-style lambda-list, setting things up so that a
34 ;;; compiler error happens if the syntax is invalid.
36 ;;; Define a function that converts a special form or other magical
37 ;;; thing into IR1. LAMBDA-LIST is a defmacro style lambda
38 ;;; list. START-VAR, NEXT-VAR and RESULT-VAR are bound to the start and
39 ;;; result continuations for the resulting IR1. KIND is the function
40 ;;; kind to associate with NAME.
41 (defmacro def-ir1-translator (name (lambda-list start-var next-var result-var)
43 (let ((fn-name (symbolicate "IR1-CONVERT-" name))
46 (multiple-value-bind (body decls doc)
47 (parse-defmacro lambda-list n-form body name "special form"
49 :error-fun 'compiler-error
52 (declaim (ftype (function (ctran ctran (or lvar null) t) (values))
54 (defun ,fn-name (,start-var ,next-var ,result-var ,n-form
55 &aux (,n-env *lexenv*))
56 (declare (ignorable ,start-var ,next-var ,result-var))
61 `((setf (fdocumentation ',name 'function) ,doc)))
62 ;; FIXME: Evidently "there can only be one!" -- we overwrite any
63 ;; other :IR1-CONVERT value. This deserves a warning, I think.
64 (setf (info :function :ir1-convert ',name) #',fn-name)
65 ;; FIXME: rename this to SPECIAL-OPERATOR, to update it to
67 (setf (info :function :kind ',name) :special-form)
68 ;; It's nice to do this for error checking in the target
69 ;; SBCL, but it's not nice to do this when we're running in
70 ;; the cross-compilation host Lisp, which owns the
71 ;; SYMBOL-FUNCTION of its COMMON-LISP symbols.
73 (let ((fun (lambda (&rest rest)
74 (declare (ignore rest))
75 (error 'special-form-function :name ',name))))
76 (setf (%simple-fun-arglist fun) ',lambda-list)
77 (setf (symbol-function ',name) fun))
80 ;;; (This is similar to DEF-IR1-TRANSLATOR, except that we pass if the
81 ;;; syntax is invalid.)
83 ;;; Define a macro-like source-to-source transformation for the
84 ;;; function NAME. A source transform may "pass" by returning a
85 ;;; non-nil second value. If the transform passes, then the form is
86 ;;; converted as a normal function call. If the supplied arguments are
87 ;;; not compatible with the specified LAMBDA-LIST, then the transform
88 ;;; automatically passes.
90 ;;; Source transforms may only be defined for functions. Source
91 ;;; transformation is not attempted if the function is declared
92 ;;; NOTINLINE. Source transforms should not examine their arguments.
93 ;;; If it matters how the function is used, then DEFTRANSFORM should
94 ;;; be used to define an IR1 transformation.
96 ;;; If the desirability of the transformation depends on the current
97 ;;; OPTIMIZE parameters, then the POLICY macro should be used to
98 ;;; determine when to pass.
99 (defmacro source-transform-lambda (lambda-list &body body)
100 (let ((n-form (gensym))
103 (multiple-value-bind (body decls)
104 (parse-defmacro lambda-list n-form body "source transform" "form"
106 :error-fun `(lambda (&rest stuff)
107 (declare (ignore stuff))
111 `(lambda (,n-form &aux (,n-env *lexenv*))
115 (defmacro define-source-transform (name lambda-list &body body)
116 `(setf (info :function :source-transform ',name)
117 (source-transform-lambda ,lambda-list ,@body)))
119 ;;;; boolean attribute utilities
121 ;;;; We need to maintain various sets of boolean attributes for known
122 ;;;; functions and VOPs. To save space and allow for quick set
123 ;;;; operations, we represent the attributes as bits in a fixnum.
125 (deftype attributes () 'fixnum)
127 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
129 ;;; Given a list of attribute names and an alist that translates them
130 ;;; to masks, return the OR of the masks.
131 (defun compute-attribute-mask (names alist)
132 (collect ((res 0 logior))
134 (let ((mask (cdr (assoc name alist))))
136 (error "unknown attribute name: ~S" name))
142 ;;; Define a new class of boolean attributes, with the attributes
143 ;;; having the specified ATTRIBUTE-NAMES. NAME is the name of the
144 ;;; class, which is used to generate some macros to manipulate sets of
147 ;;; NAME-attributep attributes attribute-name*
148 ;;; Return true if one of the named attributes is present, false
149 ;;; otherwise. When set with SETF, updates the place Attributes
150 ;;; setting or clearing the specified attributes.
152 ;;; NAME-attributes attribute-name*
153 ;;; Return a set of the named attributes.
156 (def!macro !def-boolean-attribute (name &rest attribute-names)
158 (let ((translations-name (symbolicate "*" name "-ATTRIBUTE-TRANSLATIONS*"))
159 (test-name (symbolicate name "-ATTRIBUTEP"))
160 (decoder-name (symbolicate "DECODE-" name "-ATTRIBUTES")))
162 (do ((mask 1 (ash mask 1))
163 (names attribute-names (cdr names)))
165 (alist (cons (car names) mask)))
167 (eval-when (:compile-toplevel :load-toplevel :execute)
168 (defparameter ,translations-name ',(alist)))
169 (defmacro ,(symbolicate name "-ATTRIBUTES") (&rest attribute-names)
170 "Automagically generated boolean attribute creation function.
171 See !DEF-BOOLEAN-ATTRIBUTE."
172 (compute-attribute-mask attribute-names ,translations-name))
173 (defmacro ,test-name (attributes &rest attribute-names)
174 "Automagically generated boolean attribute test function.
175 See !DEF-BOOLEAN-ATTRIBUTE."
176 `(logtest ,(compute-attribute-mask attribute-names
178 (the attributes ,attributes)))
179 ;; This definition transforms strangely under UNCROSS, in a
180 ;; way that DEF!MACRO doesn't understand, so we delegate it
181 ;; to a submacro then define the submacro differently when
182 ;; building the xc and when building the target compiler.
183 (!def-boolean-attribute-setter ,test-name
186 (defun ,decoder-name (attributes)
187 (loop for (name . mask) in ,translations-name
188 when (logtest mask attributes)
191 ;; It seems to be difficult to express in DEF!MACRO machinery what
192 ;; to do with target-vs-host GET-SETF-EXPANSION in here, so we just
193 ;; hack it by hand, passing a different GET-SETF-EXPANSION-FUN-NAME
194 ;; in the host DEFMACRO and target DEFMACRO-MUNDANELY cases.
195 (defun guts-of-!def-boolean-attribute-setter (test-name
198 get-setf-expansion-fun-name)
199 `(define-setf-expander ,test-name (place &rest attributes
201 "Automagically generated boolean attribute setter. See
202 !DEF-BOOLEAN-ATTRIBUTE."
203 #-sb-xc-host (declare (type sb!c::lexenv env))
204 ;; FIXME: It would be better if &ENVIRONMENT arguments were
205 ;; automatically declared to have type LEXENV by the
206 ;; hairy-argument-handling code.
207 (multiple-value-bind (temps values stores set get)
208 (,get-setf-expansion-fun-name place env)
210 (error "multiple store variables for ~S" place))
211 (let ((newval (gensym))
213 (mask (compute-attribute-mask attributes ,translations-name)))
214 (values `(,@temps ,n-place)
217 `(let ((,(first stores)
219 (logior ,n-place ,mask)
220 (logand ,n-place ,(lognot mask)))))
223 `(,',test-name ,n-place ,@attributes))))))
224 ;; We define the host version here, and the just-like-it-but-different
225 ;; target version later, after DEFMACRO-MUNDANELY has been defined.
226 (defmacro !def-boolean-attribute-setter (test-name
228 &rest attribute-names)
229 (guts-of-!def-boolean-attribute-setter test-name
232 'get-setf-expansion)))
234 ;;; And now for some gratuitous pseudo-abstraction...
237 ;;; Return the union of all the sets of boolean attributes which are its
239 ;;; ATTRIBUTES-INTERSECTION
240 ;;; Return the intersection of all the sets of boolean attributes which
241 ;;; are its arguments.
243 ;;; True if the attributes present in ATTR1 are identical to
245 (defmacro attributes-union (&rest attributes)
247 (logior ,@(mapcar (lambda (x) `(the attributes ,x)) attributes))))
248 (defmacro attributes-intersection (&rest attributes)
250 (logand ,@(mapcar (lambda (x) `(the attributes ,x)) attributes))))
251 (declaim (ftype (function (attributes attributes) boolean) attributes=))
252 #!-sb-fluid (declaim (inline attributes=))
253 (defun attributes= (attr1 attr2)
256 ;;;; lambda-list parsing utilities
258 ;;;; IR1 transforms, optimizers and type inferencers need to be able
259 ;;;; to parse the IR1 representation of a function call using a
260 ;;;; standard function lambda-list.
262 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
264 ;;; Given a DEFTRANSFORM-style lambda-list, generate code that parses
265 ;;; the arguments of a combination with respect to that
266 ;;; lambda-list. BODY is the list of forms which are to be
267 ;;; evaluated within the bindings. ARGS is the variable that holds
268 ;;; list of argument lvars. ERROR-FORM is a form which is evaluated
269 ;;; when the syntax of the supplied arguments is incorrect or a
270 ;;; non-constant argument keyword is supplied. Defaults and other gunk
271 ;;; are ignored. The second value is a list of all the arguments
272 ;;; bound. We make the variables IGNORABLE so that we don't have to
273 ;;; manually declare them IGNORE if their only purpose is to make the
275 (defun parse-deftransform (lambda-list body args error-form)
276 (multiple-value-bind (req opt restp rest keyp keys allowp)
277 (parse-lambda-list lambda-list)
278 (let* ((min-args (length req))
279 (max-args (+ min-args (length opt)))
287 (binds `(,arg (nth ,(pos) ,args)))
291 (let ((var (if (atom arg) arg (first arg))))
293 (binds `(,var (nth ,(pos) ,args)))
298 (binds `(,rest (nthcdr ,(pos) ,args))))
301 (if (or (atom spec) (atom (first spec)))
302 (let* ((var (if (atom spec) spec (first spec)))
303 (key (keywordicate var)))
305 (binds `(,var (find-keyword-lvar ,n-keys ,key)))
307 (let* ((head (first spec))
311 (binds `(,var (find-keyword-lvar ,n-keys ,key)))
314 (let ((n-length (gensym))
315 (limited-legal (not (or restp keyp))))
317 `(let ((,n-length (length ,args))
318 ,@(when keyp `((,n-keys (nthcdr ,(pos) ,args)))))
320 ;; FIXME: should be PROPER-LIST-OF-LENGTH-P
322 `(<= ,min-args ,n-length ,max-args)
323 `(<= ,min-args ,n-length))
326 `((check-key-args-constant ,n-keys))
327 `((check-transform-keys ,n-keys ',(keywords))))))
330 (declare (ignorable ,@(vars)))
338 ;;; Define an IR1 transformation for NAME. An IR1 transformation
339 ;;; computes a lambda that replaces the function variable reference
340 ;;; for the call. A transform may pass (decide not to transform the
341 ;;; call) by calling the GIVE-UP-IR1-TRANSFORM function. LAMBDA-LIST
342 ;;; both determines how the current call is parsed and specifies the
343 ;;; LAMBDA-LIST for the resulting lambda.
345 ;;; We parse the call and bind each of the lambda-list variables to
346 ;;; the lvar which represents the value of the argument. When parsing
347 ;;; the call, we ignore the defaults, and always bind the variables
348 ;;; for unsupplied arguments to NIL. If a required argument is
349 ;;; missing, an unknown keyword is supplied, or an argument keyword is
350 ;;; not a constant, then the transform automatically passes. The
351 ;;; DECLARATIONS apply to the bindings made by DEFTRANSFORM at
352 ;;; transformation time, rather than to the variables of the resulting
353 ;;; lambda. Bound-but-not-referenced warnings are suppressed for the
354 ;;; lambda-list variables. The DOC-STRING is used when printing
355 ;;; efficiency notes about the defined transform.
357 ;;; Normally, the body evaluates to a form which becomes the body of
358 ;;; an automatically constructed lambda. We make LAMBDA-LIST the
359 ;;; lambda-list for the lambda, and automatically insert declarations
360 ;;; of the argument and result types. If the second value of the body
361 ;;; is non-null, then it is a list of declarations which are to be
362 ;;; inserted at the head of the lambda. Automatic lambda generation
363 ;;; may be inhibited by explicitly returning a lambda from the body.
365 ;;; The ARG-TYPES and RESULT-TYPE are used to create a function type
366 ;;; which the call must satisfy before transformation is attempted.
367 ;;; The function type specifier is constructed by wrapping (FUNCTION
368 ;;; ...) around these values, so the lack of a restriction may be
369 ;;; specified by omitting the argument or supplying *. The argument
370 ;;; syntax specified in the ARG-TYPES need not be the same as that in
371 ;;; the LAMBDA-LIST, but the transform will never happen if the
372 ;;; syntaxes can't be satisfied simultaneously. If there is an
373 ;;; existing transform for the same function that has the same type,
374 ;;; then it is replaced with the new definition.
376 ;;; These are the legal keyword options:
377 ;;; :RESULT - A variable which is bound to the result lvar.
378 ;;; :NODE - A variable which is bound to the combination node for the call.
379 ;;; :POLICY - A form which is supplied to the POLICY macro to determine
380 ;;; whether this transformation is appropriate. If the result
381 ;;; is false, then the transform automatically gives up.
383 ;;; - The name and argument/result types are actually forms to be
384 ;;; evaluated. Useful for getting closures that transform similar
387 ;;; - Don't actually instantiate a transform, instead just DEFUN
388 ;;; Name with the specified transform definition function. This
389 ;;; may be later instantiated with %DEFTRANSFORM.
391 ;;; - If supplied and non-NIL, note this transform as ``important,''
392 ;;; which means efficiency notes will be generated when this
393 ;;; transform fails even if INHIBIT-WARNINGS=SPEED (but not if
394 ;;; INHIBIT-WARNINGS>SPEED).
395 (defmacro deftransform (name (lambda-list &optional (arg-types '*)
397 &key result policy node defun-only
399 &body body-decls-doc)
400 (when (and eval-name defun-only)
401 (error "can't specify both DEFUN-ONLY and EVAL-NAME"))
402 (multiple-value-bind (body decls doc) (parse-body body-decls-doc)
403 (let ((n-args (gensym))
404 (n-node (or node (gensym)))
407 (decls-body `(,@decls ,@body)))
408 (multiple-value-bind (parsed-form vars)
409 (parse-deftransform lambda-list
411 `((unless (policy ,n-node ,policy)
412 (give-up-ir1-transform))
416 '(give-up-ir1-transform))
419 (let* ((,n-args (basic-combination-args ,n-node))
421 `((,result (node-lvar ,n-node)))))
422 (multiple-value-bind (,n-lambda ,n-decls)
424 (if (and (consp ,n-lambda) (eq (car ,n-lambda) 'lambda))
426 `(lambda ,',lambda-list
427 (declare (ignorable ,@',vars))
431 `(defun ,name ,@(when doc `(,doc)) ,@stuff)
433 ,(if eval-name name `',name)
435 ``(function ,,arg-types ,,result-type)
436 `'(function ,arg-types ,result-type))
439 ,(if important t nil))))))))
441 ;;;; DEFKNOWN and DEFOPTIMIZER
443 ;;; This macro should be the way that all implementation independent
444 ;;; information about functions is made known to the compiler.
446 ;;; FIXME: The comment above suggests that perhaps some of my added
447 ;;; FTYPE declarations are in poor taste. Should I change my
448 ;;; declarations, or change the comment, or what?
450 ;;; FIXME: DEFKNOWN is needed only at build-the-system time. Figure
451 ;;; out some way to keep it from appearing in the target system.
453 ;;; Declare the function NAME to be a known function. We construct a
454 ;;; type specifier for the function by wrapping (FUNCTION ...) around
455 ;;; the ARG-TYPES and RESULT-TYPE. ATTRIBUTES is an unevaluated list
456 ;;; of boolean attributes of the function. See their description in
457 ;;; (!DEF-BOOLEAN-ATTRIBUTE IR1). NAME may also be a list of names, in
458 ;;; which case the same information is given to all the names. The
459 ;;; keywords specify the initial values for various optimizers that
460 ;;; the function might have.
461 (defmacro defknown (name arg-types result-type &optional (attributes '(any))
463 (when (and (intersection attributes '(any call unwind))
464 (intersection attributes '(movable)))
465 (error "function cannot have both good and bad attributes: ~S" attributes))
467 (when (member 'any attributes)
468 (setq attributes (union '(call unsafe unwind) attributes)))
469 (when (member 'flushable attributes)
470 (pushnew 'unsafely-flushable attributes))
472 `(%defknown ',(if (and (consp name)
473 (not (legal-fun-name-p name)))
476 '(sfunction ,arg-types ,result-type)
477 (ir1-attributes ,@attributes)
480 ;;; Create a function which parses combination args according to WHAT
481 ;;; and LAMBDA-LIST, where WHAT is either a function name or a list
482 ;;; (FUN-NAME KIND) and does some KIND of optimization.
484 ;;; The FUN-NAME must name a known function. LAMBDA-LIST is used
485 ;;; to parse the arguments to the combination as in DEFTRANSFORM. If
486 ;;; the argument syntax is invalid or there are non-constant keys,
487 ;;; then we simply return NIL.
489 ;;; The function is DEFUN'ed as FUNCTION-KIND-OPTIMIZER. Possible
490 ;;; kinds are DERIVE-TYPE, OPTIMIZER, LTN-ANNOTATE and IR2-CONVERT. If
491 ;;; a symbol is specified instead of a (FUNCTION KIND) list, then we
492 ;;; just do a DEFUN with the symbol as its name, and don't do anything
493 ;;; with the definition. This is useful for creating optimizers to be
494 ;;; passed by name to DEFKNOWN.
496 ;;; If supplied, NODE-VAR is bound to the combination node being
497 ;;; optimized. If additional VARS are supplied, then they are used as
498 ;;; the rest of the optimizer function's lambda-list. LTN-ANNOTATE
499 ;;; methods are passed an additional POLICY argument, and IR2-CONVERT
500 ;;; methods are passed an additional IR2-BLOCK argument.
501 (defmacro defoptimizer (what (lambda-list &optional (n-node (gensym))
504 (let ((name (if (symbolp what) what
505 (symbolicate (first what) "-" (second what) "-OPTIMIZER"))))
507 (let ((n-args (gensym)))
509 (defun ,name (,n-node ,@vars)
510 (declare (ignorable ,@vars))
511 (let ((,n-args (basic-combination-args ,n-node)))
512 ,(parse-deftransform lambda-list body n-args
513 `(return-from ,name nil))))
515 `((setf (,(let ((*package* (symbol-package 'sb!c::fun-info)))
516 (symbolicate "FUN-INFO-" (second what)))
517 (fun-info-or-lose ',(first what)))
520 ;;;; IR groveling macros
522 ;;; Iterate over the blocks in a component, binding BLOCK-VAR to each
523 ;;; block in turn. The value of ENDS determines whether to iterate
524 ;;; over dummy head and tail blocks:
525 ;;; NIL -- Skip Head and Tail (the default)
526 ;;; :HEAD -- Do head but skip tail
527 ;;; :TAIL -- Do tail but skip head
528 ;;; :BOTH -- Do both head and tail
530 ;;; If supplied, RESULT-FORM is the value to return.
531 (defmacro do-blocks ((block-var component &optional ends result) &body body)
532 (unless (member ends '(nil :head :tail :both))
533 (error "losing ENDS value: ~S" ends))
534 (let ((n-component (gensym))
536 `(let* ((,n-component ,component)
537 (,n-tail ,(if (member ends '(:both :tail))
539 `(component-tail ,n-component))))
540 (do ((,block-var ,(if (member ends '(:both :head))
541 `(component-head ,n-component)
542 `(block-next (component-head ,n-component)))
543 (block-next ,block-var)))
544 ((eq ,block-var ,n-tail) ,result)
546 ;;; like DO-BLOCKS, only iterating over the blocks in reverse order
547 (defmacro do-blocks-backwards ((block-var component &optional ends result) &body body)
548 (unless (member ends '(nil :head :tail :both))
549 (error "losing ENDS value: ~S" ends))
550 (let ((n-component (gensym))
552 `(let* ((,n-component ,component)
553 (,n-head ,(if (member ends '(:both :head))
555 `(component-head ,n-component))))
556 (do ((,block-var ,(if (member ends '(:both :tail))
557 `(component-tail ,n-component)
558 `(block-prev (component-tail ,n-component)))
559 (block-prev ,block-var)))
560 ((eq ,block-var ,n-head) ,result)
563 ;;; Iterate over the uses of LVAR, binding NODE to each one
566 ;;; XXX Could change it not to replicate the code someday perhaps...
567 (defmacro do-uses ((node-var lvar &optional result) &body body)
568 (with-unique-names (uses)
569 `(let ((,uses (lvar-uses ,lvar)))
571 (dolist (,node-var ,uses ,result)
574 (let ((,node-var ,uses))
577 ;;; Iterate over the nodes in BLOCK, binding NODE-VAR to the each node
578 ;;; and LVAR-VAR to the node's LVAR. The only keyword option is
579 ;;; RESTART-P, which causes iteration to be restarted when a node is
580 ;;; deleted out from under us. (If not supplied, this is an error.)
582 ;;; In the forward case, we terminate when NODE does not have NEXT, so
583 ;;; that we do not have to worry about our termination condition being
584 ;;; changed when new code is added during the iteration. In the
585 ;;; backward case, we do NODE-PREV before evaluating the body so that
586 ;;; we can keep going when the current node is deleted.
588 ;;; When RESTART-P is supplied to DO-NODES, we start iterating over
589 ;;; again at the beginning of the block when we run into a ctran whose
590 ;;; block differs from the one we are trying to iterate over, either
591 ;;; because the block was split, or because a node was deleted out
592 ;;; from under us (hence its block is NIL.) If the block start is
593 ;;; deleted, we just punt. With RESTART-P, we are also more careful
594 ;;; about termination, re-indirecting the BLOCK-LAST each time.
595 (defmacro do-nodes ((node-var lvar-var block &key restart-p)
597 (with-unique-names (n-block n-start)
598 `(do* ((,n-block ,block)
599 (,n-start (block-start ,n-block))
601 (,node-var (ctran-next ,n-start)
603 `(let ((next (node-next ,node-var)))
607 ((eq (ctran-block next) ,n-block)
610 (let ((start (block-start ,n-block)))
611 (unless (eq (ctran-kind start)
614 (ctran-next start)))))
615 `(acond ((node-next ,node-var)
619 `((,lvar-var (when (valued-node-p ,node-var)
620 (node-lvar ,node-var))
621 (when (valued-node-p ,node-var)
622 (node-lvar ,node-var))))))
626 `((when (block-delete-p ,n-block)
629 ;;; Like DO-NODES, only iterating in reverse order. Should be careful
630 ;;; with block being split under us.
631 (defmacro do-nodes-backwards ((node-var lvar block &key restart-p) &body body)
632 (let ((n-block (gensym))
634 `(loop with ,n-block = ,block
635 for ,node-var = (block-last ,n-block) then
637 `(if (eq ,n-block (ctran-block ,n-prev))
639 (block-last ,n-block))
640 `(ctran-use ,n-prev))
641 for ,n-prev = (when ,node-var (node-prev ,node-var))
642 and ,lvar = (when (and ,node-var (valued-node-p ,node-var))
643 (node-lvar ,node-var))
645 `(and ,node-var (not (block-to-be-deleted-p ,n-block)))
650 (defmacro do-nodes-carefully ((node-var block) &body body)
651 (with-unique-names (n-block n-ctran)
652 `(loop with ,n-block = ,block
653 for ,n-ctran = (block-start ,n-block) then (node-next ,node-var)
654 for ,node-var = (and ,n-ctran (ctran-next ,n-ctran))
658 ;;; Bind the IR1 context variables to the values associated with NODE,
659 ;;; so that new, extra IR1 conversion related to NODE can be done
660 ;;; after the original conversion pass has finished.
661 (defmacro with-ir1-environment-from-node (node &rest forms)
662 `(flet ((closure-needing-ir1-environment-from-node ()
664 (%with-ir1-environment-from-node
666 #'closure-needing-ir1-environment-from-node)))
667 (defun %with-ir1-environment-from-node (node fun)
668 (declare (type node node) (type function fun))
669 (let ((*current-component* (node-component node))
670 (*lexenv* (node-lexenv node))
671 (*current-path* (node-source-path node)))
672 (aver-live-component *current-component*)
675 ;;; Bind the hashtables used for keeping track of global variables,
676 ;;; functions, etc. Also establish condition handlers.
677 (defmacro with-ir1-namespace (&body forms)
678 `(let ((*free-vars* (make-hash-table :test 'eq))
679 (*free-funs* (make-hash-table :test 'equal))
680 (*constants* (make-hash-table :test 'equal))
681 (*source-paths* (make-hash-table :test 'eq)))
682 (handler-bind ((compiler-error #'compiler-error-handler)
683 (style-warning #'compiler-style-warning-handler)
684 (warning #'compiler-warning-handler))
687 ;;; Look up NAME in the lexical environment namespace designated by
688 ;;; SLOT, returning the <value, T>, or <NIL, NIL> if no entry. The
689 ;;; :TEST keyword may be used to determine the name equality
691 (defmacro lexenv-find (name slot &key test)
692 (once-only ((n-res `(assoc ,name (,(let ((*package* (symbol-package 'lexenv-funs)))
693 (symbolicate "LEXENV-" slot))
695 :test ,(or test '#'eq))))
697 (values (cdr ,n-res) t)
700 (defmacro with-component-last-block ((component block) &body body)
701 (with-unique-names (old-last-block)
702 (once-only ((component component)
704 `(let ((,old-last-block (component-last-block ,component)))
706 (progn (setf (component-last-block ,component)
709 (setf (component-last-block ,component)
710 ,old-last-block))))))
713 ;;;; the EVENT statistics/trace utility
715 ;;; FIXME: This seems to be useful for troubleshooting and
716 ;;; experimentation, not for ordinary use, so it should probably
717 ;;; become conditional on SB-SHOW.
719 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
721 (defstruct (event-info (:copier nil))
722 ;; The name of this event.
723 (name (missing-arg) :type symbol)
724 ;; The string rescribing this event.
725 (description (missing-arg) :type string)
726 ;; The name of the variable we stash this in.
727 (var (missing-arg) :type symbol)
728 ;; The number of times this event has happened.
729 (count 0 :type fixnum)
730 ;; The level of significance of this event.
731 (level (missing-arg) :type unsigned-byte)
732 ;; If true, a function that gets called with the node that the event
734 (action nil :type (or function null)))
736 ;;; A hashtable from event names to event-info structures.
737 (defvar *event-info* (make-hash-table :test 'eq))
739 ;;; Return the event info for Name or die trying.
740 (declaim (ftype (function (t) event-info) event-info-or-lose))
741 (defun event-info-or-lose (name)
742 (let ((res (gethash name *event-info*)))
744 (error "~S is not the name of an event." name))
749 ;;; Return the number of times that EVENT has happened.
750 (declaim (ftype (function (symbol) fixnum) event-count))
751 (defun event-count (name)
752 (event-info-count (event-info-or-lose name)))
754 ;;; Return the function that is called when Event happens. If this is
755 ;;; null, there is no action. The function is passed the node to which
756 ;;; the event happened, or NIL if there is no relevant node. This may
757 ;;; be set with SETF.
758 (declaim (ftype (function (symbol) (or function null)) event-action))
759 (defun event-action (name)
760 (event-info-action (event-info-or-lose name)))
761 (declaim (ftype (function (symbol (or function null)) (or function null))
763 (defun %set-event-action (name new-value)
764 (setf (event-info-action (event-info-or-lose name))
766 (defsetf event-action %set-event-action)
768 ;;; Return the non-negative integer which represents the level of
769 ;;; significance of the event Name. This is used to determine whether
770 ;;; to print a message when the event happens. This may be set with
772 (declaim (ftype (function (symbol) unsigned-byte) event-level))
773 (defun event-level (name)
774 (event-info-level (event-info-or-lose name)))
775 (declaim (ftype (function (symbol unsigned-byte) unsigned-byte) %set-event-level))
776 (defun %set-event-level (name new-value)
777 (setf (event-info-level (event-info-or-lose name))
779 (defsetf event-level %set-event-level)
781 ;;; Define a new kind of event. NAME is a symbol which names the event
782 ;;; and DESCRIPTION is a string which describes the event. Level
783 ;;; (default 0) is the level of significance associated with this
784 ;;; event; it is used to determine whether to print a Note when the
786 (defmacro defevent (name description &optional (level 0))
787 (let ((var-name (symbolicate "*" name "-EVENT-INFO*")))
788 `(eval-when (:compile-toplevel :load-toplevel :execute)
790 (make-event-info :name ',name
791 :description ',description
794 (setf (gethash ',name *event-info*) ,var-name)
797 ;;; the lowest level of event that will print a note when it occurs
798 (declaim (type unsigned-byte *event-note-threshold*))
799 (defvar *event-note-threshold* 1)
801 ;;; Note that the event with the specified NAME has happened. NODE is
802 ;;; evaluated to determine the node to which the event happened.
803 (defmacro event (name &optional node)
804 ;; Increment the counter and do any action. Mumble about the event if
806 `(%event ,(event-info-var (event-info-or-lose name)) ,node))
808 ;;; Print a listing of events and their counts, sorted by the count.
809 ;;; Events that happened fewer than Min-Count times will not be
810 ;;; printed. Stream is the stream to write to.
811 (declaim (ftype (function (&optional unsigned-byte stream) (values)) event-statistics))
812 (defun event-statistics (&optional (min-count 1) (stream *standard-output*))
814 (maphash (lambda (k v)
816 (when (>= (event-info-count v) min-count)
819 (dolist (event (sort (info) #'> :key #'event-info-count))
820 (format stream "~6D: ~A~%" (event-info-count event)
821 (event-info-description event)))
825 (declaim (ftype (function nil (values)) clear-event-statistics))
826 (defun clear-event-statistics ()
827 (maphash (lambda (k v)
829 (setf (event-info-count v) 0))
833 ;;;; functions on directly-linked lists (linked through specialized
834 ;;;; NEXT operations)
836 #!-sb-fluid (declaim (inline find-in position-in))
838 ;;; Find ELEMENT in a null-terminated LIST linked by the accessor
839 ;;; function NEXT. KEY, TEST and TEST-NOT are the same as for generic
840 ;;; sequence functions.
847 (test-not #'eql not-p))
848 (declare (type function next key test test-not))
849 (when (and test-p not-p)
850 (error "It's silly to supply both :TEST and :TEST-NOT arguments."))
852 (do ((current list (funcall next current)))
854 (unless (funcall test-not (funcall key current) element)
856 (do ((current list (funcall next current)))
858 (when (funcall test (funcall key current) element)
861 ;;; Return the position of ELEMENT (or NIL if absent) in a
862 ;;; null-terminated LIST linked by the accessor function NEXT. KEY,
863 ;;; TEST and TEST-NOT are the same as for generic sequence functions.
864 (defun position-in (next
870 (test-not #'eql not-p))
871 (declare (type function next key test test-not))
872 (when (and test-p not-p)
873 (error "It's silly to supply both :TEST and :TEST-NOT arguments."))
875 (do ((current list (funcall next current))
878 (unless (funcall test-not (funcall key current) element)
880 (do ((current list (funcall next current))
883 (when (funcall test (funcall key current) element)
887 ;;; KLUDGE: This is expanded out twice, by cut-and-paste, in a
888 ;;; (DEF!MACRO FOO (..) .. CL:GET-SETF-EXPANSION ..)
890 ;;; (SB!XC:DEFMACRO FOO (..) .. SB!XC:GET-SETF-EXPANSION ..)
891 ;;; arrangement, in order to get it to work in cross-compilation. This
892 ;;; duplication should be removed, perhaps by rewriting the macro in a more
893 ;;; cross-compiler-friendly way, or perhaps just by using some (MACROLET ((FROB
894 ;;; ..)) .. FROB .. FROB) form, or perhaps by completely eliminating this macro
895 ;;; and its partner PUSH-IN, but I don't want to do it now, because the system
896 ;;; isn't running yet, so it'd be too hard to check that my changes were
897 ;;; correct -- WHN 19990806
898 (def!macro deletef-in (next place item &environment env)
899 (multiple-value-bind (temps vals stores store access)
900 (get-setf-expansion place env)
902 (error "multiple store variables for ~S" place))
903 (let ((n-item (gensym))
907 `(let* (,@(mapcar #'list temps vals)
910 (if (eq ,n-place ,n-item)
911 (let ((,(first stores) (,next ,n-place)))
913 (do ((,n-prev ,n-place ,n-current)
914 (,n-current (,next ,n-place)
916 ((eq ,n-current ,n-item)
917 (setf (,next ,n-prev)
918 (,next ,n-current)))))
920 ;;; #+SB-XC-HOST SB!XC:DEFMACRO version is in late-macros.lisp. -- WHN 19990806
922 ;;; Push ITEM onto a list linked by the accessor function NEXT that is
925 ;;; KLUDGE: This is expanded out twice, by cut-and-paste, in a
926 ;;; (DEF!MACRO FOO (..) .. CL:GET-SETF-EXPANSION ..)
928 ;;; (SB!XC:DEFMACRO FOO (..) .. SB!XC:GET-SETF-EXPANSION ..)
929 ;;; arrangement, in order to get it to work in cross-compilation. This
930 ;;; duplication should be removed, perhaps by rewriting the macro in a more
931 ;;; cross-compiler-friendly way, or perhaps just by using some (MACROLET ((FROB
932 ;;; ..)) .. FROB .. FROB) form, or perhaps by completely eliminating this macro
933 ;;; and its partner DELETEF-IN, but I don't want to do it now, because the
934 ;;; system isn't running yet, so it'd be too hard to check that my changes were
935 ;;; correct -- WHN 19990806
936 (def!macro push-in (next item place &environment env)
937 (multiple-value-bind (temps vals stores store access)
938 (get-setf-expansion place env)
940 (error "multiple store variables for ~S" place))
941 `(let (,@(mapcar #'list temps vals)
942 (,(first stores) ,item))
943 (setf (,next ,(first stores)) ,access)
946 ;;; #+SB-XC-HOST SB!XC:DEFMACRO version is in late-macros.lisp. -- WHN 19990806
948 (defmacro position-or-lose (&rest args)
949 `(or (position ,@args)
950 (error "shouldn't happen?")))
952 ;;; user-definable compiler io syntax
954 ;;; We use WITH-SANE-IO-SYNTAX to provide safe defaults, and provide
955 ;;; *COMPILER-PRINT-VARIABLE-ALIST* for user customization.
956 (defvar *compiler-print-variable-alist* nil
958 "an association list describing new bindings for special variables
959 to be used by the compiler for error-reporting, etc. Eg.
961 ((*PRINT-LENGTH* . 10) (*PRINT-LEVEL* . 6) (*PRINT-PRETTY* . NIL))
963 The variables in the CAR positions are bound to the values in the CDR
964 during the execution of some debug commands. When evaluating arbitrary
965 expressions in the debugger, the normal values of the printer control
966 variables are in effect.
968 Initially empty, *COMPILER-PRINT-VARIABLE-ALIST* is Typically used to
969 specify bindings for printer control variables.")
971 (defmacro with-compiler-io-syntax (&body forms)
972 `(with-sane-io-syntax
974 (nreverse (mapcar #'car *compiler-print-variable-alist*))
975 (nreverse (mapcar #'cdr *compiler-print-variable-alist*))