d105f777691f423e53797b9ff85dc1477a8aa024
[sbcl.git] / src / compiler / macros.lisp
1 ;;;; miscellaneous types and macros used in writing the compiler
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
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.
11
12 (in-package "SB!C")
13
14 (declaim (special *wild-type* *universal-type* *compiler-error-context*))
15
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 
22 ;;;             if policy favors.
23 ;;; :MAYBE-INLINE
24 ;;;             Retain expansion, but only use it opportunistically.
25 (deftype inlinep () '(member :inline :maybe-inline :notinline nil))
26 \f
27 ;;;; source-hacking defining forms
28
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)
33   (if (stringp datum)
34       (apply #'compiler-error datum stuff)
35       (compiler-error "~A"
36                       (if (symbolp datum)
37                           (apply #'make-condition datum stuff)
38                           datum))))
39
40 ;;; Parse a DEFMACRO-style lambda-list, setting things up so that a
41 ;;; compiler error happens if the syntax is invalid.
42 ;;;
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))
50                                    &body body)
51   (let ((fn-name (symbolicate "IR1-CONVERT-" name))
52         (n-form (gensym))
53         (n-env (gensym)))
54     (multiple-value-bind (body decls doc)
55         (parse-defmacro lambda-list n-form body name "special form"
56                         :environment n-env
57                         :error-fun 'convert-condition-into-compiler-error
58                         :wrap-block nil)
59       `(progn
60          (declaim (ftype (function (continuation continuation t) (values))
61                          ,fn-name))
62          (defun ,fn-name (,start-var ,cont-var ,n-form)
63            (let ((,n-env *lexenv*))
64              ,@decls
65              ,body
66              (values)))
67          ,@(when doc
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.
77          #-sb-xc-host
78          ,@(when (eq kind :special-form)
79              `((setf (symbol-function ',name)
80                      (lambda (&rest rest)
81                        (declare (ignore rest))
82                        (error 'special-form-function
83                               :name ',name)))))))))
84
85 ;;; (This is similar to DEF-IR1-TRANSLATOR, except that we pass if the
86 ;;; syntax is invalid.)
87 ;;;
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.
94 ;;;
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.
100 ;;;
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))
106         (n-env (gensym))
107         (name (gensym)))
108     (multiple-value-bind (body decls)
109         (parse-defmacro lambda-list n-form body "source transform" "form"
110                         :environment n-env
111                         :error-fun `(lambda (&rest stuff)
112                                       (declare (ignore stuff))
113                                       (return-from ,name
114                                         (values nil t)))
115                         :wrap-block nil)
116       `(lambda (,n-form &aux (,n-env *lexenv*))
117          ,@decls
118          (block ,name
119            ,body)))))
120 (defmacro define-source-transform (name lambda-list &body body)
121   `(setf (info :function :source-transform ',name)
122          (source-transform-lambda ,lambda-list ,@body)))
123 \f
124 ;;;; boolean attribute utilities
125 ;;;;
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.
129
130 (deftype attributes () 'fixnum)
131
132 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
133
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))
138     (dolist (name names)
139       (let ((mask (cdr (assoc name alist))))
140         (unless mask
141           (error "unknown attribute name: ~S" name))
142         (res mask)))
143     (res)))
144
145 ) ; EVAL-WHEN
146
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
150 ;;; the attributes:
151 ;;;
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.
156 ;;;
157 ;;;    NAME-attributes attribute-name*
158 ;;;      Return a set of the named attributes.
159 #-sb-xc
160 (progn
161   (def!macro !def-boolean-attribute (name &rest attribute-names)
162
163     (let ((translations-name (symbolicate "*" name "-ATTRIBUTE-TRANSLATIONS*"))
164           (test-name (symbolicate name "-ATTRIBUTEP")))
165       (collect ((alist))
166         (do ((mask 1 (ash mask 1))
167              (names attribute-names (cdr names)))
168             ((null names))
169           (alist (cons (car names) mask)))
170         `(progn
171            (eval-when (:compile-toplevel :load-toplevel :execute)
172              (defparameter ,translations-name ',(alist)))
173            (defmacro ,(symbolicate name "-ATTRIBUTES") (&rest attribute-names)
174              "Automagically generated boolean attribute creation function.
175   See !DEF-BOOLEAN-ATTRIBUTE."
176              (compute-attribute-mask attribute-names ,translations-name))
177            (defmacro ,test-name (attributes &rest attribute-names)
178              "Automagically generated boolean attribute test function.
179   See !DEF-BOOLEAN-ATTRIBUTE."
180              `(logtest ,(compute-attribute-mask attribute-names
181                                                 ,translations-name)
182                        (the attributes ,attributes)))
183            ;; This definition transforms strangely under UNCROSS, in a
184            ;; way that DEF!MACRO doesn't understand, so we delegate it
185            ;; to a submacro then define the submacro differently when
186            ;; building the xc and when building the target compiler.
187            (!def-boolean-attribute-setter ,test-name
188                                           ,translations-name
189                                           ,@attribute-names)))))
190
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
196                                                 translations-name
197                                                 attribute-names
198                                                 get-setf-expansion-fun-name)
199     `(define-setf-expander ,test-name (place &rest attributes
200                                              &environment env)
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)
209          (when (cdr stores)
210            (error "multiple store variables for ~S" place))
211          (let ((newval (gensym))
212                (n-place (gensym))
213                (mask (compute-attribute-mask attributes ,translations-name)))
214            (values `(,@temps ,n-place)
215                    `(,@values ,get)
216                    `(,newval)
217                    `(let ((,(first stores)
218                            (if ,newval
219                                (logior ,n-place ,mask)
220                                (logand ,n-place ,(lognot mask)))))
221                       ,set
222                       ,newval)
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
227                                            translations-name
228                                            &rest attribute-names)
229     (guts-of-!def-boolean-attribute-setter test-name
230                                            translations-name
231                                            attribute-names
232                                            'get-setf-expansion)))
233
234 ;;; And now for some gratuitous pseudo-abstraction...
235 ;;;
236 ;;; ATTRIBUTES-UNION 
237 ;;;   Return the union of all the sets of boolean attributes which are its
238 ;;;   arguments.
239 ;;; ATTRIBUTES-INTERSECTION
240 ;;;   Return the intersection of all the sets of boolean attributes which
241 ;;;   are its arguments.
242 ;;; ATTRIBUTES
243 ;;;   True if the attributes present in ATTR1 are identical to
244 ;;;   those in ATTR2.
245 (defmacro attributes-union (&rest attributes)
246   `(the attributes
247         (logior ,@(mapcar (lambda (x) `(the attributes ,x)) attributes))))
248 (defmacro attributes-intersection (&rest attributes)
249   `(the 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)
254   (eql attr1 attr2))
255 \f
256 ;;;; lambda-list parsing utilities
257 ;;;;
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.
261
262 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
263
264 ;;; Given a DEFTRANSFORM-style lambda-list, generate code that parses
265 ;;; the arguments of a combination with respect to that lambda-list.
266 ;;; BODY is the the list of forms which are to be evaluated within the
267 ;;; bindings. ARGS is the variable that holds list of argument
268 ;;; continuations. ERROR-FORM is a form which is evaluated when the
269 ;;; syntax of the supplied arguments is incorrect or a non-constant
270 ;;; argument keyword is supplied. Defaults and other gunk are ignored.
271 ;;; The second value is a list of all the arguments bound. We make the
272 ;;; variables IGNORABLE so that we don't have to manually declare them
273 ;;; Ignore if their only purpose is to make the syntax work.
274 (defun parse-deftransform (lambda-list body args error-form)
275   (multiple-value-bind (req opt restp rest keyp keys allowp)
276       (parse-lambda-list lambda-list)
277     (let* ((min-args (length req))
278            (max-args (+ min-args (length opt)))
279            (n-keys (gensym)))
280       (collect ((binds)
281                 (vars)
282                 (pos 0 +)
283                 (keywords))
284         (dolist (arg req)
285           (vars arg)
286           (binds `(,arg (nth ,(pos) ,args)))
287           (pos 1))
288
289         (dolist (arg opt)
290           (let ((var (if (atom arg) arg (first  arg))))
291             (vars var)
292             (binds `(,var (nth ,(pos) ,args)))
293             (pos 1)))
294
295         (when restp
296           (vars rest)
297           (binds `(,rest (nthcdr ,(pos) ,args))))
298
299         (dolist (spec keys)
300           (if (or (atom spec) (atom (first spec)))
301               (let* ((var (if (atom spec) spec (first spec)))
302                      (key (keywordicate var)))
303                 (vars var)
304                 (binds `(,var (find-keyword-continuation ,n-keys ,key)))
305                 (keywords key))
306               (let* ((head (first spec))
307                      (var (second head))
308                      (key (first head)))
309                 (vars var)
310                 (binds `(,var (find-keyword-continuation ,n-keys ,key)))
311                 (keywords key))))
312
313         (let ((n-length (gensym))
314               (limited-legal (not (or restp keyp))))
315           (values
316            `(let ((,n-length (length ,args))
317                   ,@(when keyp `((,n-keys (nthcdr ,(pos) ,args)))))
318               (unless (and
319                        ;; FIXME: should be PROPER-LIST-OF-LENGTH-P
320                        ,(if limited-legal
321                             `(<= ,min-args ,n-length ,max-args)
322                             `(<= ,min-args ,n-length))
323                        ,@(when keyp
324                            (if allowp
325                                `((check-key-args-constant ,n-keys))
326                                `((check-transform-keys ,n-keys ',(keywords))))))
327                 ,error-form)
328               (let ,(binds)
329                 (declare (ignorable ,@(vars)))
330                 ,@body))
331            (vars)))))))
332
333 ) ; EVAL-WHEN
334 \f
335 ;;;; DEFTRANSFORM
336
337 ;;; Define an IR1 transformation for NAME. An IR1 transformation
338 ;;; computes a lambda that replaces the function variable reference
339 ;;; for the call. A transform may pass (decide not to transform the
340 ;;; call) by calling the GIVE-UP-IR1-TRANSFORM function. LAMBDA-LIST
341 ;;; both determines how the current call is parsed and specifies the
342 ;;; LAMBDA-LIST for the resulting lambda.
343 ;;;
344 ;;; We parse the call and bind each of the lambda-list variables to
345 ;;; the continuation which represents the value of the argument. When
346 ;;; parsing the call, we ignore the defaults, and always bind the
347 ;;; variables for unsupplied arguments to NIL. If a required argument
348 ;;; is missing, an unknown keyword is supplied, or an argument keyword
349 ;;; is not a constant, then the transform automatically passes. The
350 ;;; DECLARATIONS apply to the bindings made by DEFTRANSFORM at
351 ;;; transformation time, rather than to the variables of the resulting
352 ;;; lambda. Bound-but-not-referenced warnings are suppressed for the
353 ;;; lambda-list variables. The DOC-STRING is used when printing
354 ;;; efficiency notes about the defined transform.
355 ;;;
356 ;;; Normally, the body evaluates to a form which becomes the body of
357 ;;; an automatically constructed lambda. We make LAMBDA-LIST the
358 ;;; lambda-list for the lambda, and automatically insert declarations
359 ;;; of the argument and result types. If the second value of the body
360 ;;; is non-null, then it is a list of declarations which are to be
361 ;;; inserted at the head of the lambda. Automatic lambda generation
362 ;;; may be inhibited by explicitly returning a lambda from the body.
363 ;;;
364 ;;; The ARG-TYPES and RESULT-TYPE are used to create a function type
365 ;;; which the call must satisfy before transformation is attempted.
366 ;;; The function type specifier is constructed by wrapping (FUNCTION
367 ;;; ...) around these values, so the lack of a restriction may be
368 ;;; specified by omitting the argument or supplying *. The argument
369 ;;; syntax specified in the ARG-TYPES need not be the same as that in
370 ;;; the LAMBDA-LIST, but the transform will never happen if the
371 ;;; syntaxes can't be satisfied simultaneously. If there is an
372 ;;; existing transform for the same function that has the same type,
373 ;;; then it is replaced with the new definition.
374 ;;;
375 ;;; These are the legal keyword options:
376 ;;;   :RESULT - A variable which is bound to the result continuation.
377 ;;;   :NODE   - A variable which is bound to the combination node for the call.
378 ;;;   :POLICY - A form which is supplied to the POLICY macro to determine
379 ;;;             whether this transformation is appropriate. If the result
380 ;;;             is false, then the transform automatically gives up.
381 ;;;   :EVAL-NAME
382 ;;;           - The name and argument/result types are actually forms to be
383 ;;;             evaluated. Useful for getting closures that transform similar
384 ;;;             functions.
385 ;;;   :DEFUN-ONLY
386 ;;;           - Don't actually instantiate a transform, instead just DEFUN
387 ;;;             Name with the specified transform definition function. This
388 ;;;             may be later instantiated with %DEFTRANSFORM.
389 ;;;   :IMPORTANT
390 ;;;           - If supplied and non-NIL, note this transform as ``important,''
391 ;;;             which means efficiency notes will be generated when this
392 ;;;             transform fails even if INHIBIT-WARNINGS=SPEED (but not if
393 ;;;             INHIBIT-WARNINGS>SPEED).
394 (defmacro deftransform (name (lambda-list &optional (arg-types '*)
395                                           (result-type '*)
396                                           &key result policy node defun-only
397                                           eval-name important)
398                              &body body-decls-doc)
399   (when (and eval-name defun-only)
400     (error "can't specify both DEFUN-ONLY and EVAL-NAME"))
401   (multiple-value-bind (body decls doc) (parse-body body-decls-doc)
402     (let ((n-args (gensym))
403           (n-node (or node (gensym)))
404           (n-decls (gensym))
405           (n-lambda (gensym))
406           (decls-body `(,@decls ,@body)))
407       (multiple-value-bind (parsed-form vars)
408           (parse-deftransform lambda-list
409                               (if policy
410                                   `((unless (policy ,n-node ,policy)
411                                       (give-up-ir1-transform))
412                                     ,@decls-body)
413                                   body)
414                               n-args
415                               '(give-up-ir1-transform))
416         (let ((stuff
417                `((,n-node)
418                  (let* ((,n-args (basic-combination-args ,n-node))
419                         ,@(when result
420                             `((,result (node-cont ,n-node)))))
421                    (multiple-value-bind (,n-lambda ,n-decls)
422                        ,parsed-form
423                      (if (and (consp ,n-lambda) (eq (car ,n-lambda) 'lambda))
424                          ,n-lambda
425                        `(lambda ,',lambda-list
426                           (declare (ignorable ,@',vars))
427                           ,@,n-decls
428                           ,,n-lambda)))))))
429           (if defun-only
430               `(defun ,name ,@(when doc `(,doc)) ,@stuff)
431               `(%deftransform
432                 ,(if eval-name name `',name)
433                 ,(if eval-name
434                      ``(function ,,arg-types ,,result-type)
435                      `'(function ,arg-types ,result-type))
436                 (lambda ,@stuff)
437                 ,doc
438                 ,(if important t nil))))))))
439 \f
440 ;;;; DEFKNOWN and DEFOPTIMIZER
441
442 ;;; This macro should be the way that all implementation independent
443 ;;; information about functions is made known to the compiler.
444 ;;;
445 ;;; FIXME: The comment above suggests that perhaps some of my added
446 ;;; FTYPE declarations are in poor taste. Should I change my
447 ;;; declarations, or change the comment, or what?
448 ;;;
449 ;;; FIXME: DEFKNOWN is needed only at build-the-system time. Figure
450 ;;; out some way to keep it from appearing in the target system.
451 ;;;
452 ;;; Declare the function NAME to be a known function. We construct a
453 ;;; type specifier for the function by wrapping (FUNCTION ...) around
454 ;;; the ARG-TYPES and RESULT-TYPE. ATTRIBUTES is an unevaluated list
455 ;;; of boolean attributes of the function. See their description in
456 ;;; (!DEF-BOOLEAN-ATTRIBUTE IR1). NAME may also be a list of names, in
457 ;;; which case the same information is given to all the names. The
458 ;;; keywords specify the initial values for various optimizers that
459 ;;; the function might have.
460 (defmacro defknown (name arg-types result-type &optional (attributes '(any))
461                     &rest keys)
462   (when (and (intersection attributes '(any call unwind))
463              (intersection attributes '(movable)))
464     (error "function cannot have both good and bad attributes: ~S" attributes))
465
466   (when (member 'any attributes)
467     (setq attributes (union '(call unsafe unwind) attributes)))
468   (when (member 'flushable attributes)
469     (pushnew 'unsafely-flushable attributes))
470
471   `(%defknown ',(if (and (consp name)
472                          (not (legal-fun-name-p name)))
473                     name
474                     (list name))
475               '(sfunction ,arg-types ,result-type)
476               (ir1-attributes ,@attributes)
477               ,@keys))
478
479 ;;; Create a function which parses combination args according to WHAT
480 ;;; and LAMBDA-LIST, where WHAT is either a function name or a list
481 ;;; (FUN-NAME KIND) and does some KIND of optimization.
482 ;;;
483 ;;; The FUN-NAME must name a known function. LAMBDA-LIST is used
484 ;;; to parse the arguments to the combination as in DEFTRANSFORM. If
485 ;;; the argument syntax is invalid or there are non-constant keys,
486 ;;; then we simply return NIL.
487 ;;;
488 ;;; The function is DEFUN'ed as FUNCTION-KIND-OPTIMIZER. Possible
489 ;;; kinds are DERIVE-TYPE, OPTIMIZER, LTN-ANNOTATE and IR2-CONVERT. If
490 ;;; a symbol is specified instead of a (FUNCTION KIND) list, then we
491 ;;; just do a DEFUN with the symbol as its name, and don't do anything
492 ;;; with the definition. This is useful for creating optimizers to be
493 ;;; passed by name to DEFKNOWN.
494 ;;;
495 ;;; If supplied, NODE-VAR is bound to the combination node being
496 ;;; optimized. If additional VARS are supplied, then they are used as
497 ;;; the rest of the optimizer function's lambda-list. LTN-ANNOTATE
498 ;;; methods are passed an additional POLICY argument, and IR2-CONVERT
499 ;;; methods are passed an additional IR2-BLOCK argument.
500 (defmacro defoptimizer (what (lambda-list &optional (n-node (gensym))
501                                           &rest vars)
502                              &body body)
503   (let ((name (if (symbolp what) what
504                   (symbolicate (first what) "-" (second what) "-OPTIMIZER"))))
505
506     (let ((n-args (gensym)))
507       `(progn
508         (defun ,name (,n-node ,@vars)
509           (let ((,n-args (basic-combination-args ,n-node)))
510             ,(parse-deftransform lambda-list body n-args
511                                  `(return-from ,name nil))))
512         ,@(when (consp what)
513             `((setf (,(symbolicate "FUN-INFO-" (second what))
514                      (fun-info-or-lose ',(first what)))
515                     #',name)))))))
516 \f
517 ;;;; IR groveling macros
518
519 ;;; Iterate over the blocks in a component, binding BLOCK-VAR to each
520 ;;; block in turn. The value of ENDS determines whether to iterate
521 ;;; over dummy head and tail blocks:
522 ;;;    NIL  -- Skip Head and Tail (the default)
523 ;;;   :HEAD -- Do head but skip tail
524 ;;;   :TAIL -- Do tail but skip head
525 ;;;   :BOTH -- Do both head and tail
526 ;;;
527 ;;; If supplied, RESULT-FORM is the value to return.
528 (defmacro do-blocks ((block-var component &optional ends result) &body body)
529   (unless (member ends '(nil :head :tail :both))
530     (error "losing ENDS value: ~S" ends))
531   (let ((n-component (gensym))
532         (n-tail (gensym)))
533     `(let* ((,n-component ,component)
534             (,n-tail ,(if (member ends '(:both :tail))
535                           nil
536                           `(component-tail ,n-component))))
537        (do ((,block-var ,(if (member ends '(:both :head))
538                              `(component-head ,n-component)
539                              `(block-next (component-head ,n-component)))
540                         (block-next ,block-var)))
541            ((eq ,block-var ,n-tail) ,result)
542          ,@body))))
543 ;;; like DO-BLOCKS, only iterating over the blocks in reverse order
544 (defmacro do-blocks-backwards ((block-var component &optional ends result) &body body)
545   (unless (member ends '(nil :head :tail :both))
546     (error "losing ENDS value: ~S" ends))
547   (let ((n-component (gensym))
548         (n-head (gensym)))
549     `(let* ((,n-component ,component)
550             (,n-head ,(if (member ends '(:both :head))
551                           nil
552                           `(component-head ,n-component))))
553        (do ((,block-var ,(if (member ends '(:both :tail))
554                              `(component-tail ,n-component)
555                              `(block-prev (component-tail ,n-component)))
556                         (block-prev ,block-var)))
557            ((eq ,block-var ,n-head) ,result)
558          ,@body))))
559
560 ;;; Iterate over the uses of CONTINUATION, binding NODE to each one
561 ;;; successively.
562 ;;;
563 ;;; XXX Could change it not to replicate the code someday perhaps...
564 (defmacro do-uses ((node-var continuation &optional result) &body body)
565   (once-only ((n-cont continuation))
566     `(ecase (continuation-kind ,n-cont)
567        (:unused)
568        (:inside-block
569         (block nil
570           (let ((,node-var (continuation-use ,n-cont)))
571             ,@body
572             ,result)))
573        ((:block-start :deleted-block-start)
574         (dolist (,node-var (block-start-uses (continuation-block ,n-cont))
575                            ,result)
576           ,@body)))))
577
578 ;;; Iterate over the nodes in BLOCK, binding NODE-VAR to the each node
579 ;;; and CONT-VAR to the node's CONT. The only keyword option is
580 ;;; RESTART-P, which causes iteration to be restarted when a node is
581 ;;; deleted out from under us. (If not supplied, this is an error.)
582 ;;;
583 ;;; In the forward case, we terminate on LAST-CONT so that we don't
584 ;;; have to worry about our termination condition being changed when
585 ;;; new code is added during the iteration. In the backward case, we
586 ;;; do NODE-PREV before evaluating the body so that we can keep going
587 ;;; when the current node is deleted.
588 ;;;
589 ;;; When RESTART-P is supplied to DO-NODES, we start iterating over
590 ;;; again at the beginning of the block when we run into a
591 ;;; continuation whose block differs from the one we are trying to
592 ;;; iterate over, either because the block was split, or because a
593 ;;; node was deleted out from under us (hence its block is NIL.) If
594 ;;; the block start is deleted, we just punt. With RESTART-P, we are
595 ;;; also more careful about termination, re-indirecting the BLOCK-LAST
596 ;;; each time.
597 (defmacro do-nodes ((node-var cont-var block &key restart-p) &body body)
598   (let ((n-block (gensym))
599         (n-last-cont (gensym)))
600     `(let* ((,n-block ,block)
601             ,@(unless restart-p
602                 `((,n-last-cont (node-cont (block-last ,n-block))))))
603        (do* ((,node-var (continuation-next (block-start ,n-block))
604                         ,(if restart-p
605                              `(cond
606                                ((eq (continuation-block ,cont-var) ,n-block)
607                                 (aver (continuation-next ,cont-var))
608                                 (continuation-next ,cont-var))
609                                (t
610                                 (let ((start (block-start ,n-block)))
611                                   (unless (eq (continuation-kind start)
612                                               :block-start)
613                                     (return nil))
614                                   (continuation-next start))))
615                              `(continuation-next ,cont-var)))
616              (,cont-var (node-cont ,node-var) (node-cont ,node-var)))
617             (())
618          (declare (type node ,node-var))
619          ,@body
620          (when ,(if restart-p
621                     `(or (eq ,node-var (block-last ,n-block))
622                          (block-delete-p ,n-block))
623                     `(eq ,cont-var ,n-last-cont))
624            (return nil))))))
625 ;;; like DO-NODES, only iterating in reverse order
626 (defmacro do-nodes-backwards ((node-var cont-var block) &body body)
627   (let ((n-block (gensym))
628         (n-start (gensym))
629         (n-last (gensym))
630         (n-next (gensym)))
631     `(let* ((,n-block ,block)
632             (,n-start (block-start ,n-block))
633             (,n-last (block-last ,n-block)))
634        (do* ((,cont-var (node-cont ,n-last) ,n-next)
635              (,node-var ,n-last (continuation-use ,cont-var))
636              (,n-next (node-prev ,node-var) (node-prev ,node-var)))
637             (())
638          ,@body
639          (when (eq ,n-next ,n-start)
640            (return nil))))))
641
642 (defmacro do-nodes-carefully ((node-var cont-var block) &body body)
643   (with-unique-names (n-block n-last)
644     `(loop with ,n-block = ,block
645            with ,n-last = (block-last ,n-block)
646            for ,cont-var = (block-start ,n-block) then (node-cont ,node-var)
647            for ,node-var = (and ,cont-var (continuation-next ,cont-var))
648            while ,node-var
649            do (progn ,@body)
650            until (eq ,node-var ,n-last))))
651
652 ;;; Bind the IR1 context variables to the values associated with NODE,
653 ;;; so that new, extra IR1 conversion related to NODE can be done
654 ;;; after the original conversion pass has finished.
655 (defmacro with-ir1-environment-from-node (node &rest forms)
656   `(flet ((closure-needing-ir1-environment-from-node ()
657             ,@forms))
658      (%with-ir1-environment-from-node
659       ,node
660       #'closure-needing-ir1-environment-from-node)))
661 (defun %with-ir1-environment-from-node (node fun)
662   (declare (type node node) (type function fun))
663   (let ((*current-component* (node-component node))
664         (*lexenv* (node-lexenv node))
665         (*current-path* (node-source-path node)))
666     (aver-live-component *current-component*)
667     (funcall fun)))
668
669 ;;; Bind the hashtables used for keeping track of global variables,
670 ;;; functions, etc. Also establish condition handlers.
671 (defmacro with-ir1-namespace (&body forms)
672   `(let ((*free-vars* (make-hash-table :test 'eq))
673          (*free-funs* (make-hash-table :test 'equal))
674          (*constants* (make-hash-table :test 'equal))
675          (*source-paths* (make-hash-table :test 'eq)))
676      (handler-bind ((compiler-error #'compiler-error-handler)
677                     (style-warning #'compiler-style-warning-handler)
678                     (warning #'compiler-warning-handler))
679        ,@forms)))
680
681 ;;; Look up NAME in the lexical environment namespace designated by
682 ;;; SLOT, returning the <value, T>, or <NIL, NIL> if no entry. The
683 ;;; :TEST keyword may be used to determine the name equality
684 ;;; predicate.
685 (defmacro lexenv-find (name slot &key test)
686   (once-only ((n-res `(assoc ,name (,(let ((*package* (symbol-package 'lexenv-funs)))
687                                           (symbolicate "LEXENV-" slot))
688                                      *lexenv*)
689                              :test ,(or test '#'eq))))
690     `(if ,n-res
691          (values (cdr ,n-res) t)
692          (values nil nil))))
693
694 (defmacro with-component-last-block ((component block) &body body)
695   (with-unique-names (old-last-block)
696     (once-only ((component component)
697                 (block block))
698       `(let ((,old-last-block (component-last-block ,component)))
699          (unwind-protect
700               (progn (setf (component-last-block ,component)
701                            ,block)
702                      ,@body)
703            (setf (component-last-block ,component)
704                  ,old-last-block))))))
705
706 \f
707 ;;;; the EVENT statistics/trace utility
708
709 ;;; FIXME: This seems to be useful for troubleshooting and
710 ;;; experimentation, not for ordinary use, so it should probably
711 ;;; become conditional on SB-SHOW.
712
713 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
714
715 (defstruct (event-info (:copier nil))
716   ;; The name of this event.
717   (name (missing-arg) :type symbol)
718   ;; The string rescribing this event.
719   (description (missing-arg) :type string)
720   ;; The name of the variable we stash this in.
721   (var (missing-arg) :type symbol)
722   ;; The number of times this event has happened.
723   (count 0 :type fixnum)
724   ;; The level of significance of this event.
725   (level (missing-arg) :type unsigned-byte)
726   ;; If true, a function that gets called with the node that the event
727   ;; happened to.
728   (action nil :type (or function null)))
729
730 ;;; A hashtable from event names to event-info structures.
731 (defvar *event-info* (make-hash-table :test 'eq))
732
733 ;;; Return the event info for Name or die trying.
734 (declaim (ftype (function (t) event-info) event-info-or-lose))
735 (defun event-info-or-lose (name)
736   (let ((res (gethash name *event-info*)))
737     (unless res
738       (error "~S is not the name of an event." name))
739     res))
740
741 ) ; EVAL-WHEN
742
743 ;;; Return the number of times that EVENT has happened.
744 (declaim (ftype (function (symbol) fixnum) event-count))
745 (defun event-count (name)
746   (event-info-count (event-info-or-lose name)))
747
748 ;;; Return the function that is called when Event happens. If this is
749 ;;; null, there is no action. The function is passed the node to which
750 ;;; the event happened, or NIL if there is no relevant node. This may
751 ;;; be set with SETF.
752 (declaim (ftype (function (symbol) (or function null)) event-action))
753 (defun event-action (name)
754   (event-info-action (event-info-or-lose name)))
755 (declaim (ftype (function (symbol (or function null)) (or function null))
756                 %set-event-action))
757 (defun %set-event-action (name new-value)
758   (setf (event-info-action (event-info-or-lose name))
759         new-value))
760 (defsetf event-action %set-event-action)
761
762 ;;; Return the non-negative integer which represents the level of
763 ;;; significance of the event Name. This is used to determine whether
764 ;;; to print a message when the event happens. This may be set with
765 ;;; SETF.
766 (declaim (ftype (function (symbol) unsigned-byte) event-level))
767 (defun event-level (name)
768   (event-info-level (event-info-or-lose name)))
769 (declaim (ftype (function (symbol unsigned-byte) unsigned-byte) %set-event-level))
770 (defun %set-event-level (name new-value)
771   (setf (event-info-level (event-info-or-lose name))
772         new-value))
773 (defsetf event-level %set-event-level)
774
775 ;;; Define a new kind of event. NAME is a symbol which names the event
776 ;;; and DESCRIPTION is a string which describes the event. Level
777 ;;; (default 0) is the level of significance associated with this
778 ;;; event; it is used to determine whether to print a Note when the
779 ;;; event happens.
780 (defmacro defevent (name description &optional (level 0))
781   (let ((var-name (symbolicate "*" name "-EVENT-INFO*")))
782     `(eval-when (:compile-toplevel :load-toplevel :execute)
783        (defvar ,var-name
784          (make-event-info :name ',name
785                           :description ',description
786                           :var ',var-name
787                           :level ,level))
788        (setf (gethash ',name *event-info*) ,var-name)
789        ',name)))
790
791 ;;; the lowest level of event that will print a note when it occurs
792 (declaim (type unsigned-byte *event-note-threshold*))
793 (defvar *event-note-threshold* 1)
794
795 ;;; Note that the event with the specified NAME has happened. NODE is
796 ;;; evaluated to determine the node to which the event happened.
797 (defmacro event (name &optional node)
798   ;; Increment the counter and do any action. Mumble about the event if
799   ;; policy indicates.
800   `(%event ,(event-info-var (event-info-or-lose name)) ,node))
801
802 ;;; Print a listing of events and their counts, sorted by the count.
803 ;;; Events that happened fewer than Min-Count times will not be
804 ;;; printed. Stream is the stream to write to.
805 (declaim (ftype (function (&optional unsigned-byte stream) (values)) event-statistics))
806 (defun event-statistics (&optional (min-count 1) (stream *standard-output*))
807   (collect ((info))
808     (maphash (lambda (k v)
809                (declare (ignore k))
810                (when (>= (event-info-count v) min-count)
811                  (info v)))
812              *event-info*)
813     (dolist (event (sort (info) #'> :key #'event-info-count))
814       (format stream "~6D: ~A~%" (event-info-count event)
815               (event-info-description event)))
816     (values))
817   (values))
818
819 (declaim (ftype (function nil (values)) clear-event-statistics))
820 (defun clear-event-statistics ()
821   (maphash (lambda (k v)
822              (declare (ignore k))
823              (setf (event-info-count v) 0))
824            *event-info*)
825   (values))
826 \f
827 ;;;; functions on directly-linked lists (linked through specialized
828 ;;;; NEXT operations)
829
830 #!-sb-fluid (declaim (inline find-in position-in))
831
832 ;;; Find ELEMENT in a null-terminated LIST linked by the accessor
833 ;;; function NEXT. KEY, TEST and TEST-NOT are the same as for generic
834 ;;; sequence functions.
835 (defun find-in (next
836                 element
837                 list
838                 &key
839                 (key #'identity)
840                 (test #'eql test-p)
841                 (test-not #'eql not-p))
842   (declare (type function next key test test-not))
843   (when (and test-p not-p)
844     (error "It's silly to supply both :TEST and :TEST-NOT arguments."))
845   (if not-p
846       (do ((current list (funcall next current)))
847           ((null current) nil)
848         (unless (funcall test-not (funcall key current) element)
849           (return current)))
850       (do ((current list (funcall next current)))
851           ((null current) nil)
852         (when (funcall test (funcall key current) element)
853           (return current)))))
854
855 ;;; Return the position of ELEMENT (or NIL if absent) in a
856 ;;; null-terminated LIST linked by the accessor function NEXT. KEY,
857 ;;; TEST and TEST-NOT are the same as for generic sequence functions.
858 (defun position-in (next
859                     element
860                     list
861                     &key
862                     (key #'identity)
863                     (test #'eql test-p)
864                     (test-not #'eql not-p))
865   (declare (type function next key test test-not))
866   (when (and test-p not-p)
867     (error "It's silly to supply both :TEST and :TEST-NOT arguments."))
868   (if not-p
869       (do ((current list (funcall next current))
870            (i 0 (1+ i)))
871           ((null current) nil)
872         (unless (funcall test-not (funcall key current) element)
873           (return i)))
874       (do ((current list (funcall next current))
875            (i 0 (1+ i)))
876           ((null current) nil)
877         (when (funcall test (funcall key current) element)
878           (return i)))))
879
880
881 ;;; KLUDGE: This is expanded out twice, by cut-and-paste, in a
882 ;;;   (DEF!MACRO FOO (..) .. CL:GET-SETF-EXPANSION ..)
883 ;;;   #+SB-XC-HOST
884 ;;;   (SB!XC:DEFMACRO FOO (..) .. SB!XC:GET-SETF-EXPANSION ..)
885 ;;; arrangement, in order to get it to work in cross-compilation. This
886 ;;; duplication should be removed, perhaps by rewriting the macro in a more
887 ;;; cross-compiler-friendly way, or perhaps just by using some (MACROLET ((FROB
888 ;;; ..)) .. FROB .. FROB) form, or perhaps by completely eliminating this macro
889 ;;; and its partner PUSH-IN, but I don't want to do it now, because the system
890 ;;; isn't running yet, so it'd be too hard to check that my changes were
891 ;;; correct -- WHN 19990806
892 (def!macro deletef-in (next place item &environment env)
893   (multiple-value-bind (temps vals stores store access)
894       (get-setf-expansion place env)
895     (when (cdr stores)
896       (error "multiple store variables for ~S" place))
897     (let ((n-item (gensym))
898           (n-place (gensym))
899           (n-current (gensym))
900           (n-prev (gensym)))
901       `(let* (,@(mapcar #'list temps vals)
902               (,n-place ,access)
903               (,n-item ,item))
904          (if (eq ,n-place ,n-item)
905              (let ((,(first stores) (,next ,n-place)))
906                ,store)
907              (do ((,n-prev ,n-place ,n-current)
908                   (,n-current (,next ,n-place)
909                               (,next ,n-current)))
910                  ((eq ,n-current ,n-item)
911                   (setf (,next ,n-prev)
912                         (,next ,n-current)))))
913          (values)))))
914 ;;; #+SB-XC-HOST SB!XC:DEFMACRO version is in late-macros.lisp. -- WHN 19990806
915
916 ;;; Push ITEM onto a list linked by the accessor function NEXT that is
917 ;;; stored in PLACE.
918 ;;;
919 ;;; KLUDGE: This is expanded out twice, by cut-and-paste, in a
920 ;;;   (DEF!MACRO FOO (..) .. CL:GET-SETF-EXPANSION ..)
921 ;;;   #+SB-XC-HOST
922 ;;;   (SB!XC:DEFMACRO FOO (..) .. SB!XC:GET-SETF-EXPANSION ..)
923 ;;; arrangement, in order to get it to work in cross-compilation. This
924 ;;; duplication should be removed, perhaps by rewriting the macro in a more
925 ;;; cross-compiler-friendly way, or perhaps just by using some (MACROLET ((FROB
926 ;;; ..)) .. FROB .. FROB) form, or perhaps by completely eliminating this macro
927 ;;; and its partner DELETEF-IN, but I don't want to do it now, because the
928 ;;; system isn't running yet, so it'd be too hard to check that my changes were
929 ;;; correct -- WHN 19990806
930 (def!macro push-in (next item place &environment env)
931   (multiple-value-bind (temps vals stores store access)
932       (get-setf-expansion place env)
933     (when (cdr stores)
934       (error "multiple store variables for ~S" place))
935     `(let (,@(mapcar #'list temps vals)
936            (,(first stores) ,item))
937        (setf (,next ,(first stores)) ,access)
938        ,store
939        (values))))
940 ;;; #+SB-XC-HOST SB!XC:DEFMACRO version is in late-macros.lisp. -- WHN 19990806
941
942 (defmacro position-or-lose (&rest args)
943   `(or (position ,@args)
944        (error "shouldn't happen?")))