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 (deftype inlinep () '(member :inline :maybe-inline :notinline nil))
27 ;;;; source-hacking defining forms
29 ;;; to be passed to PARSE-DEFMACRO when we want compiler errors
30 ;;; instead of real errors
31 #!-sb-fluid (declaim (inline convert-condition-into-compiler-error))
32 (defun convert-condition-into-compiler-error (datum &rest stuff)
34 (apply #'compiler-error datum stuff)
37 (apply #'make-condition datum stuff)
40 ;;; Parse a DEFMACRO-style lambda-list, setting things up so that a
41 ;;; compiler error happens if the syntax is invalid.
43 ;;; Define a function that converts a special form or other magical
44 ;;; thing into IR1. LAMBDA-LIST is a defmacro style lambda list.
45 ;;; START-VAR and CONT-VAR are bound to the start and result
46 ;;; continuations for the resulting IR1. KIND is the function kind to
47 ;;; associate with NAME.
48 (defmacro def-ir1-translator (name (lambda-list start-var next-var result-var
49 &key (kind :special-form))
51 (let ((fn-name (symbolicate "IR1-CONVERT-" name))
54 (multiple-value-bind (body decls doc)
55 (parse-defmacro lambda-list n-form body name "special form"
57 :error-fun 'convert-condition-into-compiler-error
60 (declaim (ftype (function (ctran ctran (or lvar null) t) (values))
62 (defun ,fn-name (,start-var ,next-var ,result-var ,n-form)
63 (let ((,n-env *lexenv*))
68 `((setf (fdocumentation ',name 'function) ,doc)))
69 ;; FIXME: Evidently "there can only be one!" -- we overwrite any
70 ;; other :IR1-CONVERT value. This deserves a warning, I think.
71 (setf (info :function :ir1-convert ',name) #',fn-name)
72 (setf (info :function :kind ',name) ,kind)
73 ;; It's nice to do this for error checking in the target
74 ;; SBCL, but it's not nice to do this when we're running in
75 ;; the cross-compilation host Lisp, which owns the
76 ;; SYMBOL-FUNCTION of its COMMON-LISP symbols.
78 ,@(when (eq kind :special-form)
79 `((setf (symbol-function ',name)
81 (declare (ignore rest))
82 (error 'special-form-function
85 ;;; (This is similar to DEF-IR1-TRANSLATOR, except that we pass if the
86 ;;; syntax is invalid.)
88 ;;; Define a macro-like source-to-source transformation for the
89 ;;; function NAME. A source transform may "pass" by returning a
90 ;;; non-nil second value. If the transform passes, then the form is
91 ;;; converted as a normal function call. If the supplied arguments are
92 ;;; not compatible with the specified LAMBDA-LIST, then the transform
93 ;;; automatically passes.
95 ;;; Source transforms may only be defined for functions. Source
96 ;;; transformation is not attempted if the function is declared
97 ;;; NOTINLINE. Source transforms should not examine their arguments.
98 ;;; If it matters how the function is used, then DEFTRANSFORM should
99 ;;; be used to define an IR1 transformation.
101 ;;; If the desirability of the transformation depends on the current
102 ;;; OPTIMIZE parameters, then the POLICY macro should be used to
103 ;;; determine when to pass.
104 (defmacro source-transform-lambda (lambda-list &body body)
105 (let ((n-form (gensym))
108 (multiple-value-bind (body decls)
109 (parse-defmacro lambda-list n-form body "source transform" "form"
111 :error-fun `(lambda (&rest stuff)
112 (declare (ignore stuff))
116 `(lambda (,n-form &aux (,n-env *lexenv*))
120 (defmacro define-source-transform (name lambda-list &body body)
121 `(setf (info :function :source-transform ',name)
122 (source-transform-lambda ,lambda-list ,@body)))
124 ;;;; boolean attribute utilities
126 ;;;; We need to maintain various sets of boolean attributes for known
127 ;;;; functions and VOPs. To save space and allow for quick set
128 ;;;; operations, we represent the attributes as bits in a fixnum.
130 (deftype attributes () 'fixnum)
132 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
134 ;;; Given a list of attribute names and an alist that translates them
135 ;;; to masks, return the OR of the masks.
136 (defun compute-attribute-mask (names alist)
137 (collect ((res 0 logior))
139 (let ((mask (cdr (assoc name alist))))
141 (error "unknown attribute name: ~S" name))
147 ;;; Define a new class of boolean attributes, with the attributes
148 ;;; having the specified ATTRIBUTE-NAMES. NAME is the name of the
149 ;;; class, which is used to generate some macros to manipulate sets of
152 ;;; NAME-attributep attributes attribute-name*
153 ;;; Return true if one of the named attributes is present, false
154 ;;; otherwise. When set with SETF, updates the place Attributes
155 ;;; setting or clearing the specified attributes.
157 ;;; NAME-attributes attribute-name*
158 ;;; Return a set of the named attributes.
161 (def!macro !def-boolean-attribute (name &rest attribute-names)
163 (let ((translations-name (symbolicate "*" name "-ATTRIBUTE-TRANSLATIONS*"))
164 (test-name (symbolicate name "-ATTRIBUTEP"))
165 (decoder-name (symbolicate "DECODE-" name "-ATTRIBUTES")))
167 (do ((mask 1 (ash mask 1))
168 (names attribute-names (cdr names)))
170 (alist (cons (car names) mask)))
172 (eval-when (:compile-toplevel :load-toplevel :execute)
173 (defparameter ,translations-name ',(alist)))
174 (defmacro ,(symbolicate name "-ATTRIBUTES") (&rest attribute-names)
175 "Automagically generated boolean attribute creation function.
176 See !DEF-BOOLEAN-ATTRIBUTE."
177 (compute-attribute-mask attribute-names ,translations-name))
178 (defmacro ,test-name (attributes &rest attribute-names)
179 "Automagically generated boolean attribute test function.
180 See !DEF-BOOLEAN-ATTRIBUTE."
181 `(logtest ,(compute-attribute-mask attribute-names
183 (the attributes ,attributes)))
184 ;; This definition transforms strangely under UNCROSS, in a
185 ;; way that DEF!MACRO doesn't understand, so we delegate it
186 ;; to a submacro then define the submacro differently when
187 ;; building the xc and when building the target compiler.
188 (!def-boolean-attribute-setter ,test-name
191 (defun ,decoder-name (attributes)
192 (loop for (name . mask) in ,translations-name
193 when (logtest mask attributes)
196 ;; It seems to be difficult to express in DEF!MACRO machinery what
197 ;; to do with target-vs-host GET-SETF-EXPANSION in here, so we just
198 ;; hack it by hand, passing a different GET-SETF-EXPANSION-FUN-NAME
199 ;; in the host DEFMACRO and target DEFMACRO-MUNDANELY cases.
200 (defun guts-of-!def-boolean-attribute-setter (test-name
203 get-setf-expansion-fun-name)
204 `(define-setf-expander ,test-name (place &rest attributes
206 "Automagically generated boolean attribute setter. See
207 !DEF-BOOLEAN-ATTRIBUTE."
208 #-sb-xc-host (declare (type sb!c::lexenv env))
209 ;; FIXME: It would be better if &ENVIRONMENT arguments were
210 ;; automatically declared to have type LEXENV by the
211 ;; hairy-argument-handling code.
212 (multiple-value-bind (temps values stores set get)
213 (,get-setf-expansion-fun-name place env)
215 (error "multiple store variables for ~S" place))
216 (let ((newval (gensym))
218 (mask (compute-attribute-mask attributes ,translations-name)))
219 (values `(,@temps ,n-place)
222 `(let ((,(first stores)
224 (logior ,n-place ,mask)
225 (logand ,n-place ,(lognot mask)))))
228 `(,',test-name ,n-place ,@attributes))))))
229 ;; We define the host version here, and the just-like-it-but-different
230 ;; target version later, after DEFMACRO-MUNDANELY has been defined.
231 (defmacro !def-boolean-attribute-setter (test-name
233 &rest attribute-names)
234 (guts-of-!def-boolean-attribute-setter test-name
237 'get-setf-expansion)))
239 ;;; And now for some gratuitous pseudo-abstraction...
242 ;;; Return the union of all the sets of boolean attributes which are its
244 ;;; ATTRIBUTES-INTERSECTION
245 ;;; Return the intersection of all the sets of boolean attributes which
246 ;;; are its arguments.
248 ;;; True if the attributes present in ATTR1 are identical to
250 (defmacro attributes-union (&rest attributes)
252 (logior ,@(mapcar (lambda (x) `(the attributes ,x)) attributes))))
253 (defmacro attributes-intersection (&rest attributes)
255 (logand ,@(mapcar (lambda (x) `(the attributes ,x)) attributes))))
256 (declaim (ftype (function (attributes attributes) boolean) attributes=))
257 #!-sb-fluid (declaim (inline attributes=))
258 (defun attributes= (attr1 attr2)
261 ;;;; lambda-list parsing utilities
263 ;;;; IR1 transforms, optimizers and type inferencers need to be able
264 ;;;; to parse the IR1 representation of a function call using a
265 ;;;; standard function lambda-list.
267 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
269 ;;; Given a DEFTRANSFORM-style lambda-list, generate code that parses
270 ;;; the arguments of a combination with respect to that lambda-list.
271 ;;; BODY is the the list of forms which are to be evaluated within the
272 ;;; bindings. ARGS is the variable that holds list of argument
273 ;;; continuations. ERROR-FORM is a form which is evaluated when the
274 ;;; syntax of the supplied arguments is incorrect or a non-constant
275 ;;; argument keyword is supplied. Defaults and other gunk are ignored.
276 ;;; The second value is a list of all the arguments bound. We make the
277 ;;; variables IGNORABLE so that we don't have to manually declare them
278 ;;; Ignore if their only purpose is to make the syntax work.
279 (defun parse-deftransform (lambda-list body args error-form)
280 (multiple-value-bind (req opt restp rest keyp keys allowp)
281 (parse-lambda-list lambda-list)
282 (let* ((min-args (length req))
283 (max-args (+ min-args (length opt)))
291 (binds `(,arg (nth ,(pos) ,args)))
295 (let ((var (if (atom arg) arg (first arg))))
297 (binds `(,var (nth ,(pos) ,args)))
302 (binds `(,rest (nthcdr ,(pos) ,args))))
305 (if (or (atom spec) (atom (first spec)))
306 (let* ((var (if (atom spec) spec (first spec)))
307 (key (keywordicate var)))
309 (binds `(,var (find-keyword-lvar ,n-keys ,key)))
311 (let* ((head (first spec))
315 (binds `(,var (find-keyword-lvar ,n-keys ,key)))
318 (let ((n-length (gensym))
319 (limited-legal (not (or restp keyp))))
321 `(let ((,n-length (length ,args))
322 ,@(when keyp `((,n-keys (nthcdr ,(pos) ,args)))))
324 ;; FIXME: should be PROPER-LIST-OF-LENGTH-P
326 `(<= ,min-args ,n-length ,max-args)
327 `(<= ,min-args ,n-length))
330 `((check-key-args-constant ,n-keys))
331 `((check-transform-keys ,n-keys ',(keywords))))))
334 (declare (ignorable ,@(vars)))
342 ;;; Define an IR1 transformation for NAME. An IR1 transformation
343 ;;; computes a lambda that replaces the function variable reference
344 ;;; for the call. A transform may pass (decide not to transform the
345 ;;; call) by calling the GIVE-UP-IR1-TRANSFORM function. LAMBDA-LIST
346 ;;; both determines how the current call is parsed and specifies the
347 ;;; LAMBDA-LIST for the resulting lambda.
349 ;;; We parse the call and bind each of the lambda-list variables to
350 ;;; the continuation which represents the value of the argument. When
351 ;;; parsing the call, we ignore the defaults, and always bind the
352 ;;; variables for unsupplied arguments to NIL. If a required argument
353 ;;; is missing, an unknown keyword is supplied, or an argument keyword
354 ;;; is not a constant, then the transform automatically passes. The
355 ;;; DECLARATIONS apply to the bindings made by DEFTRANSFORM at
356 ;;; transformation time, rather than to the variables of the resulting
357 ;;; lambda. Bound-but-not-referenced warnings are suppressed for the
358 ;;; lambda-list variables. The DOC-STRING is used when printing
359 ;;; efficiency notes about the defined transform.
361 ;;; Normally, the body evaluates to a form which becomes the body of
362 ;;; an automatically constructed lambda. We make LAMBDA-LIST the
363 ;;; lambda-list for the lambda, and automatically insert declarations
364 ;;; of the argument and result types. If the second value of the body
365 ;;; is non-null, then it is a list of declarations which are to be
366 ;;; inserted at the head of the lambda. Automatic lambda generation
367 ;;; may be inhibited by explicitly returning a lambda from the body.
369 ;;; The ARG-TYPES and RESULT-TYPE are used to create a function type
370 ;;; which the call must satisfy before transformation is attempted.
371 ;;; The function type specifier is constructed by wrapping (FUNCTION
372 ;;; ...) around these values, so the lack of a restriction may be
373 ;;; specified by omitting the argument or supplying *. The argument
374 ;;; syntax specified in the ARG-TYPES need not be the same as that in
375 ;;; the LAMBDA-LIST, but the transform will never happen if the
376 ;;; syntaxes can't be satisfied simultaneously. If there is an
377 ;;; existing transform for the same function that has the same type,
378 ;;; then it is replaced with the new definition.
380 ;;; These are the legal keyword options:
381 ;;; :RESULT - A variable which is bound to the result continuation.
382 ;;; :NODE - A variable which is bound to the combination node for the call.
383 ;;; :POLICY - A form which is supplied to the POLICY macro to determine
384 ;;; whether this transformation is appropriate. If the result
385 ;;; is false, then the transform automatically gives up.
387 ;;; - The name and argument/result types are actually forms to be
388 ;;; evaluated. Useful for getting closures that transform similar
391 ;;; - Don't actually instantiate a transform, instead just DEFUN
392 ;;; Name with the specified transform definition function. This
393 ;;; may be later instantiated with %DEFTRANSFORM.
395 ;;; - If supplied and non-NIL, note this transform as ``important,''
396 ;;; which means efficiency notes will be generated when this
397 ;;; transform fails even if INHIBIT-WARNINGS=SPEED (but not if
398 ;;; INHIBIT-WARNINGS>SPEED).
399 (defmacro deftransform (name (lambda-list &optional (arg-types '*)
401 &key result policy node defun-only
403 &body body-decls-doc)
404 (when (and eval-name defun-only)
405 (error "can't specify both DEFUN-ONLY and EVAL-NAME"))
406 (multiple-value-bind (body decls doc) (parse-body body-decls-doc)
407 (let ((n-args (gensym))
408 (n-node (or node (gensym)))
411 (decls-body `(,@decls ,@body)))
412 (multiple-value-bind (parsed-form vars)
413 (parse-deftransform lambda-list
415 `((unless (policy ,n-node ,policy)
416 (give-up-ir1-transform))
420 '(give-up-ir1-transform))
423 (let* ((,n-args (basic-combination-args ,n-node))
425 `((,result (node-lvar ,n-node)))))
426 (multiple-value-bind (,n-lambda ,n-decls)
428 (if (and (consp ,n-lambda) (eq (car ,n-lambda) 'lambda))
430 `(lambda ,',lambda-list
431 (declare (ignorable ,@',vars))
435 `(defun ,name ,@(when doc `(,doc)) ,@stuff)
437 ,(if eval-name name `',name)
439 ``(function ,,arg-types ,,result-type)
440 `'(function ,arg-types ,result-type))
443 ,(if important t nil))))))))
445 ;;;; DEFKNOWN and DEFOPTIMIZER
447 ;;; This macro should be the way that all implementation independent
448 ;;; information about functions is made known to the compiler.
450 ;;; FIXME: The comment above suggests that perhaps some of my added
451 ;;; FTYPE declarations are in poor taste. Should I change my
452 ;;; declarations, or change the comment, or what?
454 ;;; FIXME: DEFKNOWN is needed only at build-the-system time. Figure
455 ;;; out some way to keep it from appearing in the target system.
457 ;;; Declare the function NAME to be a known function. We construct a
458 ;;; type specifier for the function by wrapping (FUNCTION ...) around
459 ;;; the ARG-TYPES and RESULT-TYPE. ATTRIBUTES is an unevaluated list
460 ;;; of boolean attributes of the function. See their description in
461 ;;; (!DEF-BOOLEAN-ATTRIBUTE IR1). NAME may also be a list of names, in
462 ;;; which case the same information is given to all the names. The
463 ;;; keywords specify the initial values for various optimizers that
464 ;;; the function might have.
465 (defmacro defknown (name arg-types result-type &optional (attributes '(any))
467 (when (and (intersection attributes '(any call unwind))
468 (intersection attributes '(movable)))
469 (error "function cannot have both good and bad attributes: ~S" attributes))
471 (when (member 'any attributes)
472 (setq attributes (union '(call unsafe unwind) attributes)))
473 (when (member 'flushable attributes)
474 (pushnew 'unsafely-flushable attributes))
476 `(%defknown ',(if (and (consp name)
477 (not (legal-fun-name-p name)))
480 '(sfunction ,arg-types ,result-type)
481 (ir1-attributes ,@attributes)
484 ;;; Create a function which parses combination args according to WHAT
485 ;;; and LAMBDA-LIST, where WHAT is either a function name or a list
486 ;;; (FUN-NAME KIND) and does some KIND of optimization.
488 ;;; The FUN-NAME must name a known function. LAMBDA-LIST is used
489 ;;; to parse the arguments to the combination as in DEFTRANSFORM. If
490 ;;; the argument syntax is invalid or there are non-constant keys,
491 ;;; then we simply return NIL.
493 ;;; The function is DEFUN'ed as FUNCTION-KIND-OPTIMIZER. Possible
494 ;;; kinds are DERIVE-TYPE, OPTIMIZER, LTN-ANNOTATE and IR2-CONVERT. If
495 ;;; a symbol is specified instead of a (FUNCTION KIND) list, then we
496 ;;; just do a DEFUN with the symbol as its name, and don't do anything
497 ;;; with the definition. This is useful for creating optimizers to be
498 ;;; passed by name to DEFKNOWN.
500 ;;; If supplied, NODE-VAR is bound to the combination node being
501 ;;; optimized. If additional VARS are supplied, then they are used as
502 ;;; the rest of the optimizer function's lambda-list. LTN-ANNOTATE
503 ;;; methods are passed an additional POLICY argument, and IR2-CONVERT
504 ;;; methods are passed an additional IR2-BLOCK argument.
505 (defmacro defoptimizer (what (lambda-list &optional (n-node (gensym))
508 (let ((name (if (symbolp what) what
509 (symbolicate (first what) "-" (second what) "-OPTIMIZER"))))
511 (let ((n-args (gensym)))
513 (defun ,name (,n-node ,@vars)
514 (let ((,n-args (basic-combination-args ,n-node)))
515 ,(parse-deftransform lambda-list body n-args
516 `(return-from ,name nil))))
518 `((setf (,(symbolicate "FUN-INFO-" (second what))
519 (fun-info-or-lose ',(first what)))
522 ;;;; IR groveling macros
524 ;;; Iterate over the blocks in a component, binding BLOCK-VAR to each
525 ;;; block in turn. The value of ENDS determines whether to iterate
526 ;;; over dummy head and tail blocks:
527 ;;; NIL -- Skip Head and Tail (the default)
528 ;;; :HEAD -- Do head but skip tail
529 ;;; :TAIL -- Do tail but skip head
530 ;;; :BOTH -- Do both head and tail
532 ;;; If supplied, RESULT-FORM is the value to return.
533 (defmacro do-blocks ((block-var component &optional ends result) &body body)
534 (unless (member ends '(nil :head :tail :both))
535 (error "losing ENDS value: ~S" ends))
536 (let ((n-component (gensym))
538 `(let* ((,n-component ,component)
539 (,n-tail ,(if (member ends '(:both :tail))
541 `(component-tail ,n-component))))
542 (do ((,block-var ,(if (member ends '(:both :head))
543 `(component-head ,n-component)
544 `(block-next (component-head ,n-component)))
545 (block-next ,block-var)))
546 ((eq ,block-var ,n-tail) ,result)
548 ;;; like DO-BLOCKS, only iterating over the blocks in reverse order
549 (defmacro do-blocks-backwards ((block-var component &optional ends result) &body body)
550 (unless (member ends '(nil :head :tail :both))
551 (error "losing ENDS value: ~S" ends))
552 (let ((n-component (gensym))
554 `(let* ((,n-component ,component)
555 (,n-head ,(if (member ends '(:both :head))
557 `(component-head ,n-component))))
558 (do ((,block-var ,(if (member ends '(:both :tail))
559 `(component-tail ,n-component)
560 `(block-prev (component-tail ,n-component)))
561 (block-prev ,block-var)))
562 ((eq ,block-var ,n-head) ,result)
565 ;;; Iterate over the uses of CONTINUATION, binding NODE to each one
568 ;;; XXX Could change it not to replicate the code someday perhaps...
569 (defmacro do-uses ((node-var lvar &optional result) &body body)
570 (with-unique-names (uses)
571 `(let ((,uses (lvar-uses ,lvar)))
573 (dolist (,node-var ,uses ,result)
576 (let ((,node-var ,uses))
579 ;;; Iterate over the nodes in BLOCK, binding NODE-VAR to the each node
580 ;;; and CONT-VAR to the node's CONT. The only keyword option is
581 ;;; RESTART-P, which causes iteration to be restarted when a node is
582 ;;; deleted out from under us. (If not supplied, this is an error.)
584 ;;; In the forward case, we terminate on LAST-CONT so that we don't
585 ;;; have to worry about our termination condition being changed when
586 ;;; new code is added during the iteration. In the backward case, we
587 ;;; do NODE-PREV before evaluating the body so that we can keep going
588 ;;; when the current node is deleted.
590 ;;; When RESTART-P is supplied to DO-NODES, we start iterating over
591 ;;; again at the beginning of the block when we run into a
592 ;;; continuation whose block differs from the one we are trying to
593 ;;; iterate over, either because the block was split, or because a
594 ;;; node was deleted out from under us (hence its block is NIL.) If
595 ;;; the block start is deleted, we just punt. With RESTART-P, we are
596 ;;; also more careful about termination, re-indirecting the BLOCK-LAST
598 (defmacro do-nodes ((node-var lvar-var block &key restart-p)
600 (with-unique-names (n-block n-start)
601 `(do* ((,n-block ,block)
602 (,n-start (block-start ,n-block))
604 (,node-var (ctran-next ,n-start)
606 `(let ((next (node-next ,node-var)))
610 ((eq (ctran-block next) ,n-block)
613 (let ((start (block-start ,n-block)))
614 (unless (eq (ctran-kind start)
617 (ctran-next start)))))
618 `(acond ((node-next ,node-var)
622 `((,lvar-var #1=(when (valued-node-p ,node-var)
623 (node-lvar ,node-var))
628 `((when (block-delete-p ,n-block)
631 ;;; like DO-NODES, only iterating in reverse order
632 (defmacro do-nodes-backwards ((node-var lvar block) &body body)
633 (let ((n-block (gensym))
636 `(do* ((,n-block ,block)
637 (,n-start (block-start ,n-block))
638 (,node-var (block-last ,n-block) (ctran-use ,n-prev))
639 (,n-prev (node-prev ,node-var) (node-prev ,node-var))
640 (,lvar #1=(when (valued-node-p ,node-var) (node-lvar ,node-var))
644 (when (eq ,n-prev ,n-start)
647 (defmacro do-nodes-carefully ((node-var block) &body body)
648 (with-unique-names (n-block n-ctran)
649 `(loop with ,n-block = ,block
650 for ,n-ctran = (block-start ,n-block) then (node-next ,node-var)
651 for ,node-var = (and ,n-ctran (ctran-next ,n-ctran))
655 ;;; Bind the IR1 context variables to the values associated with NODE,
656 ;;; so that new, extra IR1 conversion related to NODE can be done
657 ;;; after the original conversion pass has finished.
658 (defmacro with-ir1-environment-from-node (node &rest forms)
659 `(flet ((closure-needing-ir1-environment-from-node ()
661 (%with-ir1-environment-from-node
663 #'closure-needing-ir1-environment-from-node)))
664 (defun %with-ir1-environment-from-node (node fun)
665 (declare (type node node) (type function fun))
666 (let ((*current-component* (node-component node))
667 (*lexenv* (node-lexenv node))
668 (*current-path* (node-source-path node)))
669 (aver-live-component *current-component*)
672 ;;; Bind the hashtables used for keeping track of global variables,
673 ;;; functions, etc. Also establish condition handlers.
674 (defmacro with-ir1-namespace (&body forms)
675 `(let ((*free-vars* (make-hash-table :test 'eq))
676 (*free-funs* (make-hash-table :test 'equal))
677 (*constants* (make-hash-table :test 'equal))
678 (*source-paths* (make-hash-table :test 'eq)))
679 (handler-bind ((compiler-error #'compiler-error-handler)
680 (style-warning #'compiler-style-warning-handler)
681 (warning #'compiler-warning-handler))
684 ;;; Look up NAME in the lexical environment namespace designated by
685 ;;; SLOT, returning the <value, T>, or <NIL, NIL> if no entry. The
686 ;;; :TEST keyword may be used to determine the name equality
688 (defmacro lexenv-find (name slot &key test)
689 (once-only ((n-res `(assoc ,name (,(let ((*package* (symbol-package 'lexenv-funs)))
690 (symbolicate "LEXENV-" slot))
692 :test ,(or test '#'eq))))
694 (values (cdr ,n-res) t)
697 (defmacro with-component-last-block ((component block) &body body)
698 (with-unique-names (old-last-block)
699 (once-only ((component component)
701 `(let ((,old-last-block (component-last-block ,component)))
703 (progn (setf (component-last-block ,component)
706 (setf (component-last-block ,component)
707 ,old-last-block))))))
710 ;;;; the EVENT statistics/trace utility
712 ;;; FIXME: This seems to be useful for troubleshooting and
713 ;;; experimentation, not for ordinary use, so it should probably
714 ;;; become conditional on SB-SHOW.
716 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
718 (defstruct (event-info (:copier nil))
719 ;; The name of this event.
720 (name (missing-arg) :type symbol)
721 ;; The string rescribing this event.
722 (description (missing-arg) :type string)
723 ;; The name of the variable we stash this in.
724 (var (missing-arg) :type symbol)
725 ;; The number of times this event has happened.
726 (count 0 :type fixnum)
727 ;; The level of significance of this event.
728 (level (missing-arg) :type unsigned-byte)
729 ;; If true, a function that gets called with the node that the event
731 (action nil :type (or function null)))
733 ;;; A hashtable from event names to event-info structures.
734 (defvar *event-info* (make-hash-table :test 'eq))
736 ;;; Return the event info for Name or die trying.
737 (declaim (ftype (function (t) event-info) event-info-or-lose))
738 (defun event-info-or-lose (name)
739 (let ((res (gethash name *event-info*)))
741 (error "~S is not the name of an event." name))
746 ;;; Return the number of times that EVENT has happened.
747 (declaim (ftype (function (symbol) fixnum) event-count))
748 (defun event-count (name)
749 (event-info-count (event-info-or-lose name)))
751 ;;; Return the function that is called when Event happens. If this is
752 ;;; null, there is no action. The function is passed the node to which
753 ;;; the event happened, or NIL if there is no relevant node. This may
754 ;;; be set with SETF.
755 (declaim (ftype (function (symbol) (or function null)) event-action))
756 (defun event-action (name)
757 (event-info-action (event-info-or-lose name)))
758 (declaim (ftype (function (symbol (or function null)) (or function null))
760 (defun %set-event-action (name new-value)
761 (setf (event-info-action (event-info-or-lose name))
763 (defsetf event-action %set-event-action)
765 ;;; Return the non-negative integer which represents the level of
766 ;;; significance of the event Name. This is used to determine whether
767 ;;; to print a message when the event happens. This may be set with
769 (declaim (ftype (function (symbol) unsigned-byte) event-level))
770 (defun event-level (name)
771 (event-info-level (event-info-or-lose name)))
772 (declaim (ftype (function (symbol unsigned-byte) unsigned-byte) %set-event-level))
773 (defun %set-event-level (name new-value)
774 (setf (event-info-level (event-info-or-lose name))
776 (defsetf event-level %set-event-level)
778 ;;; Define a new kind of event. NAME is a symbol which names the event
779 ;;; and DESCRIPTION is a string which describes the event. Level
780 ;;; (default 0) is the level of significance associated with this
781 ;;; event; it is used to determine whether to print a Note when the
783 (defmacro defevent (name description &optional (level 0))
784 (let ((var-name (symbolicate "*" name "-EVENT-INFO*")))
785 `(eval-when (:compile-toplevel :load-toplevel :execute)
787 (make-event-info :name ',name
788 :description ',description
791 (setf (gethash ',name *event-info*) ,var-name)
794 ;;; the lowest level of event that will print a note when it occurs
795 (declaim (type unsigned-byte *event-note-threshold*))
796 (defvar *event-note-threshold* 1)
798 ;;; Note that the event with the specified NAME has happened. NODE is
799 ;;; evaluated to determine the node to which the event happened.
800 (defmacro event (name &optional node)
801 ;; Increment the counter and do any action. Mumble about the event if
803 `(%event ,(event-info-var (event-info-or-lose name)) ,node))
805 ;;; Print a listing of events and their counts, sorted by the count.
806 ;;; Events that happened fewer than Min-Count times will not be
807 ;;; printed. Stream is the stream to write to.
808 (declaim (ftype (function (&optional unsigned-byte stream) (values)) event-statistics))
809 (defun event-statistics (&optional (min-count 1) (stream *standard-output*))
811 (maphash (lambda (k v)
813 (when (>= (event-info-count v) min-count)
816 (dolist (event (sort (info) #'> :key #'event-info-count))
817 (format stream "~6D: ~A~%" (event-info-count event)
818 (event-info-description event)))
822 (declaim (ftype (function nil (values)) clear-event-statistics))
823 (defun clear-event-statistics ()
824 (maphash (lambda (k v)
826 (setf (event-info-count v) 0))
830 ;;;; functions on directly-linked lists (linked through specialized
831 ;;;; NEXT operations)
833 #!-sb-fluid (declaim (inline find-in position-in))
835 ;;; Find ELEMENT in a null-terminated LIST linked by the accessor
836 ;;; function NEXT. KEY, TEST and TEST-NOT are the same as for generic
837 ;;; sequence functions.
844 (test-not #'eql not-p))
845 (declare (type function next key test test-not))
846 (when (and test-p not-p)
847 (error "It's silly to supply both :TEST and :TEST-NOT arguments."))
849 (do ((current list (funcall next current)))
851 (unless (funcall test-not (funcall key current) element)
853 (do ((current list (funcall next current)))
855 (when (funcall test (funcall key current) element)
858 ;;; Return the position of ELEMENT (or NIL if absent) in a
859 ;;; null-terminated LIST linked by the accessor function NEXT. KEY,
860 ;;; TEST and TEST-NOT are the same as for generic sequence functions.
861 (defun position-in (next
867 (test-not #'eql not-p))
868 (declare (type function next key test test-not))
869 (when (and test-p not-p)
870 (error "It's silly to supply both :TEST and :TEST-NOT arguments."))
872 (do ((current list (funcall next current))
875 (unless (funcall test-not (funcall key current) element)
877 (do ((current list (funcall next current))
880 (when (funcall test (funcall key current) element)
884 ;;; KLUDGE: This is expanded out twice, by cut-and-paste, in a
885 ;;; (DEF!MACRO FOO (..) .. CL:GET-SETF-EXPANSION ..)
887 ;;; (SB!XC:DEFMACRO FOO (..) .. SB!XC:GET-SETF-EXPANSION ..)
888 ;;; arrangement, in order to get it to work in cross-compilation. This
889 ;;; duplication should be removed, perhaps by rewriting the macro in a more
890 ;;; cross-compiler-friendly way, or perhaps just by using some (MACROLET ((FROB
891 ;;; ..)) .. FROB .. FROB) form, or perhaps by completely eliminating this macro
892 ;;; and its partner PUSH-IN, but I don't want to do it now, because the system
893 ;;; isn't running yet, so it'd be too hard to check that my changes were
894 ;;; correct -- WHN 19990806
895 (def!macro deletef-in (next place item &environment env)
896 (multiple-value-bind (temps vals stores store access)
897 (get-setf-expansion place env)
899 (error "multiple store variables for ~S" place))
900 (let ((n-item (gensym))
904 `(let* (,@(mapcar #'list temps vals)
907 (if (eq ,n-place ,n-item)
908 (let ((,(first stores) (,next ,n-place)))
910 (do ((,n-prev ,n-place ,n-current)
911 (,n-current (,next ,n-place)
913 ((eq ,n-current ,n-item)
914 (setf (,next ,n-prev)
915 (,next ,n-current)))))
917 ;;; #+SB-XC-HOST SB!XC:DEFMACRO version is in late-macros.lisp. -- WHN 19990806
919 ;;; Push ITEM onto a list linked by the accessor function NEXT that is
922 ;;; KLUDGE: This is expanded out twice, by cut-and-paste, in a
923 ;;; (DEF!MACRO FOO (..) .. CL:GET-SETF-EXPANSION ..)
925 ;;; (SB!XC:DEFMACRO FOO (..) .. SB!XC:GET-SETF-EXPANSION ..)
926 ;;; arrangement, in order to get it to work in cross-compilation. This
927 ;;; duplication should be removed, perhaps by rewriting the macro in a more
928 ;;; cross-compiler-friendly way, or perhaps just by using some (MACROLET ((FROB
929 ;;; ..)) .. FROB .. FROB) form, or perhaps by completely eliminating this macro
930 ;;; and its partner DELETEF-IN, but I don't want to do it now, because the
931 ;;; system isn't running yet, so it'd be too hard to check that my changes were
932 ;;; correct -- WHN 19990806
933 (def!macro push-in (next item place &environment env)
934 (multiple-value-bind (temps vals stores store access)
935 (get-setf-expansion place env)
937 (error "multiple store variables for ~S" place))
938 `(let (,@(mapcar #'list temps vals)
939 (,(first stores) ,item))
940 (setf (,next ,(first stores)) ,access)
943 ;;; #+SB-XC-HOST SB!XC:DEFMACRO version is in late-macros.lisp. -- WHN 19990806
945 (defmacro position-or-lose (&rest args)
946 `(or (position ,@args)
947 (error "shouldn't happen?")))