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