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