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