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 cont-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)
59 (declaim (ftype (function (continuation continuation t) (values))
61 (defun ,fn-name (,start-var ,cont-var ,n-form)
62 (let ((,n-env *lexenv*))
67 `((setf (fdocumentation ',name 'function) ,doc)))
68 ;; FIXME: Evidently "there can only be one!" -- we overwrite any
69 ;; other :IR1-CONVERT value. This deserves a warning, I think.
70 (setf (info :function :ir1-convert ',name) #',fn-name)
71 (setf (info :function :kind ',name) ,kind)
72 ;; It's nice to do this for error checking in the target
73 ;; SBCL, but it's not nice to do this when we're running in
74 ;; the cross-compilation host Lisp, which owns the
75 ;; SYMBOL-FUNCTION of its COMMON-LISP symbols.
77 ,@(when (eq kind :special-form)
78 `((setf (symbol-function ',name)
80 (declare (ignore rest))
81 (error 'special-form-function
84 ;;; (This is similar to DEF-IR1-TRANSLATOR, except that we pass if the
85 ;;; syntax is invalid.)
87 ;;; Define a macro-like source-to-source transformation for the
88 ;;; function NAME. A source transform may "pass" by returning a
89 ;;; non-nil second value. If the transform passes, then the form is
90 ;;; converted as a normal function call. If the supplied arguments are
91 ;;; not compatible with the specified LAMBDA-LIST, then the transform
92 ;;; automatically passes.
94 ;;; Source transforms may only be defined for functions. Source
95 ;;; transformation is not attempted if the function is declared
96 ;;; NOTINLINE. Source transforms should not examine their arguments.
97 ;;; If it matters how the function is used, then DEFTRANSFORM should
98 ;;; be used to define an IR1 transformation.
100 ;;; If the desirability of the transformation depends on the current
101 ;;; OPTIMIZE parameters, then the POLICY macro should be used to
102 ;;; determine when to pass.
103 (defmacro define-source-transform (name lambda-list &body body)
110 (apply #'symbolicate "SOURCE-TRANSFORM" (pieces)))
111 (symbolicate "SOURCE-TRANSFORM-" name)))
114 (multiple-value-bind (body decls)
115 (parse-defmacro lambda-list n-form body name "form"
117 :error-fun `(lambda (&rest stuff)
118 (declare (ignore stuff))
119 (return-from ,fn-name
122 (defun ,fn-name (,n-form)
123 (let ((,n-env *lexenv*))
126 (setf (info :function :source-transform ',name) #',fn-name)))))
128 ;;;; boolean attribute utilities
130 ;;;; We need to maintain various sets of boolean attributes for known
131 ;;;; functions and VOPs. To save space and allow for quick set
132 ;;;; operations, we represent the attributes as bits in a fixnum.
134 (deftype attributes () 'fixnum)
136 (eval-when (:compile-toplevel :load-toplevel :execute)
138 ;;; Given a list of attribute names and an alist that translates them
139 ;;; to masks, return the OR of the masks.
140 (defun compute-attribute-mask (names alist)
141 (collect ((res 0 logior))
143 (let ((mask (cdr (assoc name alist))))
145 (error "unknown attribute name: ~S" name))
151 ;;; Define a new class of boolean attributes, with the attributes
152 ;;; having the specified ATTRIBUTE-NAMES. NAME is the name of the
153 ;;; class, which is used to generate some macros to manipulate sets of
156 ;;; NAME-attributep attributes attribute-name*
157 ;;; Return true if one of the named attributes is present, false
158 ;;; otherwise. When set with SETF, updates the place Attributes
159 ;;; setting or clearing the specified attributes.
161 ;;; NAME-attributes attribute-name*
162 ;;; Return a set of the named attributes.
165 (def!macro !def-boolean-attribute (name &rest attribute-names)
167 (let ((translations-name (symbolicate "*" name "-ATTRIBUTE-TRANSLATIONS*"))
168 (test-name (symbolicate name "-ATTRIBUTEP")))
170 (do ((mask 1 (ash mask 1))
171 (names attribute-names (cdr names)))
173 (alist (cons (car names) mask)))
175 (eval-when (:compile-toplevel :load-toplevel :execute)
176 (defparameter ,translations-name ',(alist)))
177 (defmacro ,(symbolicate name "-ATTRIBUTES") (&rest attribute-names)
178 "Automagically generated boolean attribute creation function.
179 See !DEF-BOOLEAN-ATTRIBUTE."
180 (compute-attribute-mask attribute-names ,translations-name))
181 (defmacro ,test-name (attributes &rest attribute-names)
182 "Automagically generated boolean attribute test function.
183 See !DEF-BOOLEAN-ATTRIBUTE."
184 `(logtest ,(compute-attribute-mask attribute-names
186 (the attributes ,attributes)))
187 ;; This definition transforms strangely under UNCROSS, in a
188 ;; way that DEF!MACRO doesn't understand, so we delegate it
189 ;; to a submacro then define the submacro differently when
190 ;; building the xc and when building the target compiler.
191 (!def-boolean-attribute-setter ,test-name
193 ,@attribute-names)))))
195 ;; It seems to be difficult to express in DEF!MACRO machinery what
196 ;; to do with target-vs-host GET-SETF-EXPANSION in here, so we just
197 ;; hack it by hand, passing a different GET-SETF-EXPANSION-FUN-NAME
198 ;; in the host DEFMACRO and target DEFMACRO-MUNDANELY cases.
199 (defun guts-of-!def-boolean-attribute-setter (test-name
202 get-setf-expansion-fun-name)
203 `(define-setf-expander ,test-name (place &rest attributes
205 "Automagically generated boolean attribute setter. See
206 !DEF-BOOLEAN-ATTRIBUTE."
207 #-sb-xc-host (declare (type sb!c::lexenv env))
208 ;; FIXME: It would be better if &ENVIRONMENT arguments were
209 ;; automatically declared to have type LEXENV by the
210 ;; hairy-argument-handling code.
211 (multiple-value-bind (temps values stores set get)
212 (,get-setf-expansion-fun-name place env)
214 (error "multiple store variables for ~S" place))
215 (let ((newval (gensym))
217 (mask (compute-attribute-mask attributes ,translations-name)))
218 (values `(,@temps ,n-place)
221 `(let ((,(first stores)
223 (logior ,n-place ,mask)
224 (logand ,n-place ,(lognot mask)))))
227 `(,',test-name ,n-place ,@attributes))))))
228 ;; We define the host version here, and the just-like-it-but-different
229 ;; target version later, after DEFMACRO-MUNDANELY has been defined.
230 (defmacro !def-boolean-attribute-setter (test-name
232 &rest attribute-names)
233 (guts-of-!def-boolean-attribute-setter test-name
236 'get-setf-expansion)))
238 ;;; And now for some gratuitous pseudo-abstraction...
241 ;;; Return the union of all the sets of boolean attributes which are its
243 ;;; ATTRIBUTES-INTERSECTION
244 ;;; Return the intersection of all the sets of boolean attributes which
245 ;;; are its arguments.
247 ;;; True if the attributes present in ATTR1 are identical to
249 (defmacro attributes-union (&rest attributes)
251 (logior ,@(mapcar (lambda (x) `(the attributes ,x)) attributes))))
252 (defmacro attributes-intersection (&rest attributes)
254 (logand ,@(mapcar (lambda (x) `(the attributes ,x)) attributes))))
255 (declaim (ftype (function (attributes attributes) boolean) attributes=))
256 #!-sb-fluid (declaim (inline attributes=))
257 (defun attributes= (attr1 attr2)
260 ;;;; lambda-list parsing utilities
262 ;;;; IR1 transforms, optimizers and type inferencers need to be able
263 ;;;; to parse the IR1 representation of a function call using a
264 ;;;; standard function lambda-list.
266 (eval-when (:compile-toplevel :load-toplevel :execute)
268 ;;; Given a DEFTRANSFORM-style lambda-list, generate code that parses
269 ;;; the arguments of a combination with respect to that lambda-list.
270 ;;; BODY is the the list of forms which are to be evaluated within the
271 ;;; bindings. ARGS is the variable that holds list of argument
272 ;;; continuations. ERROR-FORM is a form which is evaluated when the
273 ;;; syntax of the supplied arguments is incorrect or a non-constant
274 ;;; argument keyword is supplied. Defaults and other gunk are ignored.
275 ;;; The second value is a list of all the arguments bound. We make the
276 ;;; variables IGNORABLE so that we don't have to manually declare them
277 ;;; Ignore if their only purpose is to make the syntax work.
278 (defun parse-deftransform (lambda-list body args error-form)
279 (multiple-value-bind (req opt restp rest keyp keys allowp)
280 (parse-lambda-list lambda-list)
281 (let* ((min-args (length req))
282 (max-args (+ min-args (length opt)))
290 (binds `(,arg (nth ,(pos) ,args)))
294 (let ((var (if (atom arg) arg (first arg))))
296 (binds `(,var (nth ,(pos) ,args)))
301 (binds `(,rest (nthcdr ,(pos) ,args))))
304 (if (or (atom spec) (atom (first spec)))
305 (let* ((var (if (atom spec) spec (first spec)))
306 (key (keywordicate var)))
308 (binds `(,var (find-keyword-continuation ,n-keys ,key)))
310 (let* ((head (first spec))
314 (binds `(,var (find-keyword-continuation ,n-keys ,key)))
317 (let ((n-length (gensym))
318 (limited-legal (not (or restp keyp))))
320 `(let ((,n-length (length ,args))
321 ,@(when keyp `((,n-keys (nthcdr ,(pos) ,args)))))
323 ;; FIXME: should be PROPER-LIST-OF-LENGTH-P
325 `(<= ,min-args ,n-length ,max-args)
326 `(<= ,min-args ,n-length))
329 `((check-key-args-constant ,n-keys))
330 `((check-transform-keys ,n-keys ',(keywords))))))
333 (declare (ignorable ,@(vars)))
341 ;;; Define an IR1 transformation for NAME. An IR1 transformation
342 ;;; computes a lambda that replaces the function variable reference
343 ;;; for the call. A transform may pass (decide not to transform the
344 ;;; call) by calling the GIVE-UP-IR1-TRANSFORM function. LAMBDA-LIST
345 ;;; both determines how the current call is parsed and specifies the
346 ;;; LAMBDA-LIST for the resulting lambda.
348 ;;; We parse the call and bind each of the lambda-list variables to
349 ;;; the continuation which represents the value of the argument. When
350 ;;; parsing the call, we ignore the defaults, and always bind the
351 ;;; variables for unsupplied arguments to NIL. If a required argument
352 ;;; is missing, an unknown keyword is supplied, or an argument keyword
353 ;;; is not a constant, then the transform automatically passes. The
354 ;;; DECLARATIONS apply to the bindings made by DEFTRANSFORM at
355 ;;; transformation time, rather than to the variables of the resulting
356 ;;; lambda. Bound-but-not-referenced warnings are suppressed for the
357 ;;; lambda-list variables. The DOC-STRING is used when printing
358 ;;; efficiency notes about the defined transform.
360 ;;; Normally, the body evaluates to a form which becomes the body of
361 ;;; an automatically constructed lambda. We make LAMBDA-LIST the
362 ;;; lambda-list for the lambda, and automatically insert declarations
363 ;;; of the argument and result types. If the second value of the body
364 ;;; is non-null, then it is a list of declarations which are to be
365 ;;; inserted at the head of the lambda. Automatic lambda generation
366 ;;; may be inhibited by explicitly returning a lambda from the body.
368 ;;; The ARG-TYPES and RESULT-TYPE are used to create a function type
369 ;;; which the call must satisfy before transformation is attempted.
370 ;;; The function type specifier is constructed by wrapping (FUNCTION
371 ;;; ...) around these values, so the lack of a restriction may be
372 ;;; specified by omitting the argument or supplying *. The argument
373 ;;; syntax specified in the ARG-TYPES need not be the same as that in
374 ;;; the LAMBDA-LIST, but the transform will never happen if the
375 ;;; syntaxes can't be satisfied simultaneously. If there is an
376 ;;; existing transform for the same function that has the same type,
377 ;;; then it is replaced with the new definition.
379 ;;; These are the legal keyword options:
380 ;;; :RESULT - A variable which is bound to the result continuation.
381 ;;; :NODE - A variable which is bound to the combination node for the call.
382 ;;; :POLICY - A form which is supplied to the POLICY macro to determine
383 ;;; whether this transformation is appropriate. If the result
384 ;;; is false, then the transform automatically gives up.
386 ;;; - The name and argument/result types are actually forms to be
387 ;;; evaluated. Useful for getting closures that transform similar
390 ;;; - Don't actually instantiate a transform, instead just DEFUN
391 ;;; Name with the specified transform definition function. This
392 ;;; may be later instantiated with %DEFTRANSFORM.
394 ;;; - If supplied and non-NIL, note this transform as ``important,''
395 ;;; which means efficiency notes will be generated when this
396 ;;; transform fails even if INHIBIT-WARNINGS=SPEED (but not if
397 ;;; INHIBIT-WARNINGS>SPEED).
398 (defmacro deftransform (name (lambda-list &optional (arg-types '*)
400 &key result policy node defun-only
402 &body body-decls-doc)
403 (when (and eval-name defun-only)
404 (error "can't specify both DEFUN-ONLY and EVAL-NAME"))
405 (multiple-value-bind (body decls doc) (parse-body body-decls-doc)
406 (let ((n-args (gensym))
407 (n-node (or node (gensym)))
410 (decls-body `(,@decls ,@body)))
411 (multiple-value-bind (parsed-form vars)
412 (parse-deftransform lambda-list
414 `((unless (policy ,n-node ,policy)
415 (give-up-ir1-transform))
419 '(give-up-ir1-transform))
422 (let* ((,n-args (basic-combination-args ,n-node))
424 `((,result (node-cont ,n-node)))))
425 (multiple-value-bind (,n-lambda ,n-decls)
427 (if (and (consp ,n-lambda) (eq (car ,n-lambda) 'lambda))
429 `(lambda ,',lambda-list
430 (declare (ignorable ,@',vars))
434 `(defun ,name ,@(when doc `(,doc)) ,@stuff)
436 ,(if eval-name name `',name)
438 ``(function ,,arg-types ,,result-type)
439 `'(function ,arg-types ,result-type))
442 ,(if important t nil))))))))
444 ;;;; DEFKNOWN and DEFOPTIMIZER
446 ;;; This macro should be the way that all implementation independent
447 ;;; information about functions is made known to the compiler.
449 ;;; FIXME: The comment above suggests that perhaps some of my added
450 ;;; FTYPE declarations are in poor taste. Should I change my
451 ;;; declarations, or change the comment, or what?
453 ;;; FIXME: DEFKNOWN is needed only at build-the-system time. Figure
454 ;;; out some way to keep it from appearing in the target system.
456 ;;; Declare the function NAME to be a known function. We construct a
457 ;;; type specifier for the function by wrapping (FUNCTION ...) around
458 ;;; the ARG-TYPES and RESULT-TYPE. ATTRIBUTES is an unevaluated list
459 ;;; of boolean attributes of the function. See their description in
460 ;;; (!DEF-BOOLEAN-ATTRIBUTE IR1). NAME may also be a list of names, in
461 ;;; which case the same information is given to all the names. The
462 ;;; keywords specify the initial values for various optimizers that
463 ;;; the function might have.
464 (defmacro defknown (name arg-types result-type &optional (attributes '(any))
466 (when (and (intersection attributes '(any call unwind))
467 (intersection attributes '(movable)))
468 (error "function cannot have both good and bad attributes: ~S" attributes))
470 (when (member 'any attributes)
471 (setf attributes (union '(call unsafe unwind) attributes)))
472 (when (member 'flushable attributes)
473 (pushnew 'unsafely-flushable attributes))
475 `(%defknown ',(if (and (consp name)
476 (not (eq (car name) 'setf)))
479 '(function ,arg-types ,result-type)
480 (ir1-attributes ,@attributes)
483 ;;; Create a function which parses combination args according to WHAT
484 ;;; and LAMBDA-LIST, where WHAT is either a function name or a list
485 ;;; (FUN-NAME KIND) and does some KIND of optimization.
487 ;;; The FUN-NAME must name a known function. LAMBDA-LIST is used
488 ;;; to parse the arguments to the combination as in DEFTRANSFORM. If
489 ;;; the argument syntax is invalid or there are non-constant keys,
490 ;;; then we simply return NIL.
492 ;;; The function is DEFUN'ed as FUNCTION-KIND-OPTIMIZER. Possible
493 ;;; kinds are DERIVE-TYPE, OPTIMIZER, LTN-ANNOTATE and IR2-CONVERT. If
494 ;;; a symbol is specified instead of a (FUNCTION KIND) list, then we
495 ;;; just do a DEFUN with the symbol as its name, and don't do anything
496 ;;; with the definition. This is useful for creating optimizers to be
497 ;;; passed by name to DEFKNOWN.
499 ;;; If supplied, NODE-VAR is bound to the combination node being
500 ;;; optimized. If additional VARS are supplied, then they are used as
501 ;;; the rest of the optimizer function's lambda-list. LTN-ANNOTATE
502 ;;; methods are passed an additional POLICY argument, and IR2-CONVERT
503 ;;; methods are passed an additional IR2-BLOCK argument.
504 (defmacro defoptimizer (what (lambda-list &optional (n-node (gensym))
507 (let ((name (if (symbolp what) what
508 (symbolicate (first what) "-" (second what) "-OPTIMIZER"))))
510 (let ((n-args (gensym)))
512 (defun ,name (,n-node ,@vars)
513 (let ((,n-args (basic-combination-args ,n-node)))
514 ,(parse-deftransform lambda-list body n-args
515 `(return-from ,name nil))))
517 `((setf (,(symbolicate "FUN-INFO-" (second what))
518 (fun-info-or-lose ',(first what)))
521 ;;;; IR groveling macros
523 ;;; Iterate over the blocks in a component, binding BLOCK-VAR to each
524 ;;; block in turn. The value of ENDS determines whether to iterate
525 ;;; over dummy head and tail blocks:
526 ;;; NIL -- Skip Head and Tail (the default)
527 ;;; :HEAD -- Do head but skip tail
528 ;;; :TAIL -- Do tail but skip head
529 ;;; :BOTH -- Do both head and tail
531 ;;; If supplied, RESULT-FORM is the value to return.
532 (defmacro do-blocks ((block-var component &optional ends result) &body body)
533 (unless (member ends '(nil :head :tail :both))
534 (error "losing ENDS value: ~S" ends))
535 (let ((n-component (gensym))
537 `(let* ((,n-component ,component)
538 (,n-tail ,(if (member ends '(:both :tail))
540 `(component-tail ,n-component))))
541 (do ((,block-var ,(if (member ends '(:both :head))
542 `(component-head ,n-component)
543 `(block-next (component-head ,n-component)))
544 (block-next ,block-var)))
545 ((eq ,block-var ,n-tail) ,result)
547 ;;; like DO-BLOCKS, only iterating over the blocks in reverse order
548 (defmacro do-blocks-backwards ((block-var component &optional ends result) &body body)
549 (unless (member ends '(nil :head :tail :both))
550 (error "losing ENDS value: ~S" ends))
551 (let ((n-component (gensym))
553 `(let* ((,n-component ,component)
554 (,n-head ,(if (member ends '(:both :head))
556 `(component-head ,n-component))))
557 (do ((,block-var ,(if (member ends '(:both :tail))
558 `(component-tail ,n-component)
559 `(block-prev (component-tail ,n-component)))
560 (block-prev ,block-var)))
561 ((eq ,block-var ,n-head) ,result)
564 ;;; Iterate over the uses of CONTINUATION, binding NODE to each one
567 ;;; XXX Could change it not to replicate the code someday perhaps...
568 (defmacro do-uses ((node-var continuation &optional result) &body body)
569 (once-only ((n-cont continuation))
570 `(ecase (continuation-kind ,n-cont)
574 (let ((,node-var (continuation-use ,n-cont)))
577 ((:block-start :deleted-block-start)
578 (dolist (,node-var (block-start-uses (continuation-block ,n-cont))
582 ;;; Iterate over the nodes in BLOCK, binding NODE-VAR to the each node
583 ;;; and CONT-VAR to the node's CONT. The only keyword option is
584 ;;; RESTART-P, which causes iteration to be restarted when a node is
585 ;;; deleted out from under us. (If not supplied, this is an error.)
587 ;;; In the forward case, we terminate on LAST-CONT so that we don't
588 ;;; have to worry about our termination condition being changed when
589 ;;; new code is added during the iteration. In the backward case, we
590 ;;; do NODE-PREV before evaluating the body so that we can keep going
591 ;;; when the current node is deleted.
593 ;;; When RESTART-P is supplied to DO-NODES, we start iterating over
594 ;;; again at the beginning of the block when we run into a
595 ;;; continuation whose block differs from the one we are trying to
596 ;;; iterate over, either because the block was split, or because a
597 ;;; node was deleted out from under us (hence its block is NIL.) If
598 ;;; the block start is deleted, we just punt. With RESTART-P, we are
599 ;;; also more careful about termination, re-indirecting the BLOCK-LAST
601 (defmacro do-nodes ((node-var cont-var block &key restart-p) &body body)
602 (let ((n-block (gensym))
603 (n-last-cont (gensym)))
604 `(let* ((,n-block ,block)
606 `((,n-last-cont (node-cont (block-last ,n-block))))))
607 (do* ((,node-var (continuation-next (block-start ,n-block))
610 ((eq (continuation-block ,cont-var) ,n-block)
611 (aver (continuation-next ,cont-var))
612 (continuation-next ,cont-var))
614 (let ((start (block-start ,n-block)))
615 (unless (eq (continuation-kind start)
618 (continuation-next start))))
619 `(continuation-next ,cont-var)))
620 (,cont-var (node-cont ,node-var) (node-cont ,node-var)))
624 `(eq ,node-var (block-last ,n-block))
625 `(eq ,cont-var ,n-last-cont))
627 ;;; like DO-NODES, only iterating in reverse order
628 (defmacro do-nodes-backwards ((node-var cont-var block) &body body)
629 (let ((n-block (gensym))
633 `(let* ((,n-block ,block)
634 (,n-start (block-start ,n-block))
635 (,n-last (block-last ,n-block)))
636 (do* ((,cont-var (node-cont ,n-last) ,n-next)
637 (,node-var ,n-last (continuation-use ,cont-var))
638 (,n-next (node-prev ,node-var) (node-prev ,node-var)))
641 (when (eq ,n-next ,n-start)
644 ;;; Bind the IR1 context variables to the values associated with NODE,
645 ;;; so that new, extra IR1 conversion related to NODE can be done
646 ;;; after the original conversion pass has finished.
647 (defmacro with-ir1-environment-from-node (node &rest forms)
648 `(flet ((closure-needing-ir1-environment-from-node ()
650 (%with-ir1-environment-from-node
652 #'closure-needing-ir1-environment-from-node)))
653 (defun %with-ir1-environment-from-node (node fun)
654 (declare (type node node) (type function fun))
655 (let ((*current-component* (node-component node))
656 (*lexenv* (node-lexenv node))
657 (*current-path* (node-source-path node)))
658 (aver-live-component *current-component*)
661 ;;; Bind the hashtables used for keeping track of global variables,
662 ;;; functions, etc. Also establish condition handlers.
663 (defmacro with-ir1-namespace (&body forms)
664 `(let ((*free-vars* (make-hash-table :test 'eq))
665 (*free-funs* (make-hash-table :test 'equal))
666 (*constants* (make-hash-table :test 'equal))
667 (*source-paths* (make-hash-table :test 'eq)))
668 (handler-bind ((compiler-error #'compiler-error-handler)
669 (style-warning #'compiler-style-warning-handler)
670 (warning #'compiler-warning-handler))
673 ;;; Look up NAME in the lexical environment namespace designated by
674 ;;; SLOT, returning the <value, T>, or <NIL, NIL> if no entry. The
675 ;;; :TEST keyword may be used to determine the name equality
677 (defmacro lexenv-find (name slot &key test)
678 (once-only ((n-res `(assoc ,name (,(let ((*package* (symbol-package 'lexenv-funs)))
679 (symbolicate "LEXENV-" slot))
681 :test ,(or test '#'eq))))
683 (values (cdr ,n-res) t)
687 (defmacro with-continuation-type-assertion ((cont ctype context) &body body)
688 `(let ((*lexenv* (ir1ize-the-or-values ,ctype ,cont *lexenv* ,context)))
691 ;;;; the EVENT statistics/trace utility
693 ;;; FIXME: This seems to be useful for troubleshooting and
694 ;;; experimentation, not for ordinary use, so it should probably
695 ;;; become conditional on SB-SHOW.
697 (eval-when (:compile-toplevel :load-toplevel :execute)
699 (defstruct (event-info (:copier nil))
700 ;; The name of this event.
701 (name (missing-arg) :type symbol)
702 ;; The string rescribing this event.
703 (description (missing-arg) :type string)
704 ;; The name of the variable we stash this in.
705 (var (missing-arg) :type symbol)
706 ;; The number of times this event has happened.
707 (count 0 :type fixnum)
708 ;; The level of significance of this event.
709 (level (missing-arg) :type unsigned-byte)
710 ;; If true, a function that gets called with the node that the event
712 (action nil :type (or function null)))
714 ;;; A hashtable from event names to event-info structures.
715 (defvar *event-info* (make-hash-table :test 'eq))
717 ;;; Return the event info for Name or die trying.
718 (declaim (ftype (function (t) event-info) event-info-or-lose))
719 (defun event-info-or-lose (name)
720 (let ((res (gethash name *event-info*)))
722 (error "~S is not the name of an event." name))
727 ;;; Return the number of times that EVENT has happened.
728 (declaim (ftype (function (symbol) fixnum) event-count))
729 (defun event-count (name)
730 (event-info-count (event-info-or-lose name)))
732 ;;; Return the function that is called when Event happens. If this is
733 ;;; null, there is no action. The function is passed the node to which
734 ;;; the event happened, or NIL if there is no relevant node. This may
735 ;;; be set with SETF.
736 (declaim (ftype (function (symbol) (or function null)) event-action))
737 (defun event-action (name)
738 (event-info-action (event-info-or-lose name)))
739 (declaim (ftype (function (symbol (or function null)) (or function null))
741 (defun %set-event-action (name new-value)
742 (setf (event-info-action (event-info-or-lose name))
744 (defsetf event-action %set-event-action)
746 ;;; Return the non-negative integer which represents the level of
747 ;;; significance of the event Name. This is used to determine whether
748 ;;; to print a message when the event happens. This may be set with
750 (declaim (ftype (function (symbol) unsigned-byte) event-level))
751 (defun event-level (name)
752 (event-info-level (event-info-or-lose name)))
753 (declaim (ftype (function (symbol unsigned-byte) unsigned-byte) %set-event-level))
754 (defun %set-event-level (name new-value)
755 (setf (event-info-level (event-info-or-lose name))
757 (defsetf event-level %set-event-level)
759 ;;; Define a new kind of event. NAME is a symbol which names the event
760 ;;; and DESCRIPTION is a string which describes the event. Level
761 ;;; (default 0) is the level of significance associated with this
762 ;;; event; it is used to determine whether to print a Note when the
764 (defmacro defevent (name description &optional (level 0))
765 (let ((var-name (symbolicate "*" name "-EVENT-INFO*")))
766 `(eval-when (:compile-toplevel :load-toplevel :execute)
768 (make-event-info :name ',name
769 :description ',description
772 (setf (gethash ',name *event-info*) ,var-name)
775 ;;; the lowest level of event that will print a note when it occurs
776 (declaim (type unsigned-byte *event-note-threshold*))
777 (defvar *event-note-threshold* 1)
779 ;;; Note that the event with the specified NAME has happened. NODE is
780 ;;; evaluated to determine the node to which the event happened.
781 (defmacro event (name &optional node)
782 ;; Increment the counter and do any action. Mumble about the event if
784 `(%event ,(event-info-var (event-info-or-lose name)) ,node))
786 ;;; Print a listing of events and their counts, sorted by the count.
787 ;;; Events that happened fewer than Min-Count times will not be
788 ;;; printed. Stream is the stream to write to.
789 (declaim (ftype (function (&optional unsigned-byte stream) (values)) event-statistics))
790 (defun event-statistics (&optional (min-count 1) (stream *standard-output*))
792 (maphash (lambda (k v)
794 (when (>= (event-info-count v) min-count)
797 (dolist (event (sort (info) #'> :key #'event-info-count))
798 (format stream "~6D: ~A~%" (event-info-count event)
799 (event-info-description event)))
803 (declaim (ftype (function nil (values)) clear-event-statistics))
804 (defun clear-event-statistics ()
805 (maphash (lambda (k v)
807 (setf (event-info-count v) 0))
811 ;;;; functions on directly-linked lists (linked through specialized
812 ;;;; NEXT operations)
814 #!-sb-fluid (declaim (inline find-in position-in))
816 ;;; Find ELEMENT in a null-terminated LIST linked by the accessor
817 ;;; function NEXT. KEY, TEST and TEST-NOT are the same as for generic
818 ;;; sequence functions.
825 (test-not #'eql not-p))
826 (declare (type function next key test test-not))
827 (when (and test-p not-p)
828 (error "It's silly to supply both :TEST and :TEST-NOT arguments."))
830 (do ((current list (funcall next current)))
832 (unless (funcall test-not (funcall key current) element)
834 (do ((current list (funcall next current)))
836 (when (funcall test (funcall key current) element)
839 ;;; Return the position of ELEMENT (or NIL if absent) in a
840 ;;; null-terminated LIST linked by the accessor function NEXT. KEY,
841 ;;; TEST and TEST-NOT are the same as for generic sequence functions.
842 (defun position-in (next
848 (test-not #'eql not-p))
849 (declare (type function next key test test-not))
850 (when (and test-p not-p)
851 (error "It's silly to supply both :TEST and :TEST-NOT arguments."))
853 (do ((current list (funcall next current))
856 (unless (funcall test-not (funcall key current) element)
858 (do ((current list (funcall next current))
861 (when (funcall test (funcall key current) element)
865 ;;; KLUDGE: This is expanded out twice, by cut-and-paste, in a
866 ;;; (DEF!MACRO FOO (..) .. CL:GET-SETF-EXPANSION ..)
868 ;;; (SB!XC:DEFMACRO FOO (..) .. SB!XC:GET-SETF-EXPANSION ..)
869 ;;; arrangement, in order to get it to work in cross-compilation. This
870 ;;; duplication should be removed, perhaps by rewriting the macro in a more
871 ;;; cross-compiler-friendly way, or perhaps just by using some (MACROLET ((FROB
872 ;;; ..)) .. FROB .. FROB) form, or perhaps by completely eliminating this macro
873 ;;; and its partner PUSH-IN, but I don't want to do it now, because the system
874 ;;; isn't running yet, so it'd be too hard to check that my changes were
875 ;;; correct -- WHN 19990806
876 (def!macro deletef-in (next place item &environment env)
877 (multiple-value-bind (temps vals stores store access)
878 (get-setf-expansion place env)
880 (error "multiple store variables for ~S" place))
881 (let ((n-item (gensym))
885 `(let* (,@(mapcar #'list temps vals)
888 (if (eq ,n-place ,n-item)
889 (let ((,(first stores) (,next ,n-place)))
891 (do ((,n-prev ,n-place ,n-current)
892 (,n-current (,next ,n-place)
894 ((eq ,n-current ,n-item)
895 (setf (,next ,n-prev)
896 (,next ,n-current)))))
898 ;;; #+SB-XC-HOST SB!XC:DEFMACRO version is in late-macros.lisp. -- WHN 19990806
900 ;;; Push ITEM onto a list linked by the accessor function NEXT that is
903 ;;; KLUDGE: This is expanded out twice, by cut-and-paste, in a
904 ;;; (DEF!MACRO FOO (..) .. CL:GET-SETF-EXPANSION ..)
906 ;;; (SB!XC:DEFMACRO FOO (..) .. SB!XC:GET-SETF-EXPANSION ..)
907 ;;; arrangement, in order to get it to work in cross-compilation. This
908 ;;; duplication should be removed, perhaps by rewriting the macro in a more
909 ;;; cross-compiler-friendly way, or perhaps just by using some (MACROLET ((FROB
910 ;;; ..)) .. FROB .. FROB) form, or perhaps by completely eliminating this macro
911 ;;; and its partner DELETEF-IN, but I don't want to do it now, because the
912 ;;; system isn't running yet, so it'd be too hard to check that my changes were
913 ;;; correct -- WHN 19990806
914 (def!macro push-in (next item place &environment env)
915 (multiple-value-bind (temps vals stores store access)
916 (get-setf-expansion place env)
918 (error "multiple store variables for ~S" place))
919 `(let (,@(mapcar #'list temps vals)
920 (,(first stores) ,item))
921 (setf (,next ,(first stores)) ,access)
924 ;;; #+SB-XC-HOST SB!XC:DEFMACRO version is in late-macros.lisp. -- WHN 19990806
926 (defmacro position-or-lose (&rest args)
927 `(or (position ,@args)
928 (error "shouldn't happen?")))