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