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