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