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