Fix typo.
[sbcl.git] / src / compiler / macros.lisp
blobb8c8fccbc1f8ffac9ac15a00c42cd56710b14814
1 ;;;; miscellaneous types and macros used in writing the compiler
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.
12 (in-package "SB-C")
14 ;;;; DEFTYPEs
16 ;;; An INLINEP value describes how a function is called. The values
17 ;;; have these meanings:
18 ;;; NIL No declaration seen: do whatever you feel like, but don't
19 ;;; dump an inline expansion.
20 ;;; NOTINLINE NOTINLINE declaration seen: always do full function call.
21 ;;; INLINE INLINE declaration seen: save expansion, expanding to it
22 ;;; if policy favors.
23 ;;; MAYBE-INLINE
24 ;;; Retain expansion, but only use it opportunistically.
25 ;;; MAYBE-INLINE is quite different from INLINE. As explained
26 ;;; by APD on #lisp 2005-11-26: "MAYBE-INLINE lambda is
27 ;;; instantiated once per component, INLINE - for all
28 ;;; references (even under #'without FUNCALL)."
29 (deftype inlinep () '(member inline maybe-inline notinline nil))
32 ;;;; source-hacking defining forms
34 ;;; Parse a DEFMACRO-style lambda-list, setting things up so that a
35 ;;; compiler error happens if the syntax is invalid.
36 ;;;
37 ;;; Define a function that converts a special form or other magical
38 ;;; thing into IR1. LAMBDA-LIST is a defmacro style lambda
39 ;;; list. START-VAR, NEXT-VAR and RESULT-VAR are bound to the start and
40 ;;; result continuations for the resulting IR1. KIND is the function
41 ;;; kind to associate with NAME.
42 ;;; FIXME - Translators which accept implicit PROGNs fail on improper
43 ;;; input, e.g. (LAMBDA (X) (CATCH X (BAZ) . 3))
44 ;;; This is because &REST is defined to allow a dotted tail in macros,
45 ;;; and we have no implementation-specific workaround to disallow it.
46 (defmacro def-ir1-translator (name (lambda-list start-var next-var result-var)
47 &body body)
48 (binding* ((fn-name (symbolicate "IR1-CONVERT-" name))
49 (whole-var (make-symbol "FORM"))
50 ((lambda-expr doc)
51 (make-macro-lambda nil lambda-list body :special-form name
52 :doc-string-allowed :external
53 :wrap-block nil)))
54 (declare (ignorable doc)) ; unused on host
55 ;; Maybe kill docstring, but only under the cross-compiler.
56 #+(and (not sb-doc) sb-xc-host) (setq doc nil)
57 `(progn
58 (declaim (ftype (function (ctran ctran (or lvar null) t) (values))
59 ,fn-name))
60 (defun ,fn-name (,start-var ,next-var ,result-var ,whole-var)
61 (declare (ignorable ,start-var ,next-var ,result-var))
62 ;; The guard function is a closure, which can't have its lambda-list
63 ;; changed independently of other closures based on the same
64 ;; simple-fun. So change it in the ir1-translator since the actual
65 ;; lambda-list is not terribly useful.
66 (declare (lambda-list ,lambda-list))
67 (,lambda-expr ,whole-var *lexenv*)
68 (values))
69 #-sb-xc-host
70 (progn (install-guard-function ',name '(:special ,name))
71 (setf (documentation (symbol-function ',name) t) ',doc))
72 ;; FIXME: Evidently "there can only be one!" -- we overwrite any
73 ;; other :IR1-CONVERT value. This deserves a warning, I think.
74 (setf (info :function :ir1-convert ',name) #',fn-name)
75 ;; FIXME: rename this to SPECIAL-OPERATOR, to update it to
76 ;; the 1990s?
77 (setf (info :function :kind ',name) :special-form)
78 ',name)))
80 ;;; (This is similar to DEF-IR1-TRANSLATOR, except that we pass if the
81 ;;; syntax is invalid.)
82 ;;;
83 ;;; Define a macro-like source-to-source transformation for the
84 ;;; function NAME. A source transform may "pass" by returning a
85 ;;; non-nil second value. If the transform passes, then the form is
86 ;;; converted as a normal function call. If the supplied arguments are
87 ;;; not compatible with the specified LAMBDA-LIST, then the transform
88 ;;; automatically passes.
89 ;;;
90 ;;; Source transforms may only be defined for functions. Source
91 ;;; transformation is not attempted if the function is declared
92 ;;; NOTINLINE. Source transforms should not examine their arguments.
93 ;;; A macro lambda list which destructures more than one level would
94 ;;; be legal but suspicious, as inner list parsing "examines" arguments.
95 ;;; If it matters how the function is used, then DEFTRANSFORM should
96 ;;; be used to define an IR1 transformation.
97 ;;;
98 ;;; If the desirability of the transformation depends on the current
99 ;;; OPTIMIZE parameters, then the POLICY macro should be used to
100 ;;; determine when to pass.
102 ;;; Note that while a compiler-macro must deal with being invoked when its
103 ;;; whole form matches (FUNCALL <f> ...) so that it must skip over <f> to find
104 ;;; the arguments, a source-transform need not worry about that situation.
105 ;;; Any FUNCALL which is eligible for a source-transform calls the expander
106 ;;; with the form's head replaced by a compiler representation of the function.
107 ;;; Internalizing the name avoids semantic problems resulting from syntactic
108 ;;; substitution. One problem would be that a source-transform can exist for
109 ;;; a function named (SETF X), but ((SETF X) arg ...) would be bad syntax.
110 ;;; Even if we decided that it is ok within the compiler - just not in code
111 ;;; given to the compiler - the problem remains that changing (FUNCALL 'F x)
112 ;;; to (F x) is wrong when F also names a local functionoid.
113 ;;; Hence, either a #<GLOBAL-VAR> or #<DEFINED-FUN> appears in the form head.
115 (defmacro define-source-transform (fun-name lambda-list &body body)
116 ;; FIXME: this is redundant with what will become MAKE-MACRO-LAMBDA
117 ;; except that it needs a "silently do nothing" mode, which may or may not
118 ;; be a generally exposed feature.
119 (binding*
120 (((forms decls) (parse-body body nil))
121 ((llks req opt rest keys aux env whole)
122 (parse-lambda-list
123 lambda-list
124 :accept
125 (logandc2 (logior (lambda-list-keyword-mask '&environment)
126 (lambda-list-keyword-mask 'destructuring-bind))
127 ;; Function lambda lists shouldn't take &BODY.
128 (lambda-list-keyword-mask '&body))
129 :context "a source transform"))
130 ((outer-decl inner-decls) (extract-var-decls decls (append env whole)))
131 ;; With general macros, the user can declare (&WHOLE W &ENVIRONMENT E ..)
132 ;; and then (DECLARE (IGNORE W E)) which is a problem if system code
133 ;; touches user variables. But this is all system code, so it's fine.
134 (lambda-whole (if whole (car whole) (make-symbol "FORM")))
135 (lambda-env (if env (car env) (make-symbol "ENV")))
136 (new-ll (if (or whole env) ; strip them out if present
137 (make-lambda-list llks nil req opt rest keys aux)
138 lambda-list)) ; otherwise use the original list
139 (args (make-symbol "ARGS")))
140 `(%define-source-transform ',fun-name
141 (named-lambda (:source-transform ,fun-name)
142 (,lambda-whole ,lambda-env &aux (,args (cdr ,lambda-whole)))
143 ,@(if (not env) `((declare (ignore ,lambda-env))))
144 ,@outer-decl ; SPECIALs or something? I hope not.
145 (if (not ,(emit-ds-lambda-list-match args new-ll))
146 (values nil t)
147 ;; The body can return 1 or 2 values, but consistently
148 ;; returning 2 values from the XEP is stylistically
149 ;; preferable, and produces shorter assembly code too.
150 (multiple-value-bind (call pass)
151 (binding* ,(expand-ds-bind new-ll args nil 'truly-the)
152 ,@inner-decls
153 (block ,(fun-name-block-name fun-name) ,@forms))
154 (values call pass)))))))
155 (defun %define-source-transform (fun-name lambda)
156 (when (info :function :source-transform fun-name)
157 (warn "Redefining source-transform for ~S" fun-name))
158 (setf (info :function :source-transform fun-name) lambda))
160 ;;;; lambda-list parsing utilities
161 ;;;;
162 ;;;; IR1 transforms, optimizers and type inferencers need to be able
163 ;;;; to parse the IR1 representation of a function call using a
164 ;;;; standard function lambda-list.
166 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
168 ;;; Given a DEFTRANSFORM-style lambda-list, generate code that parses
169 ;;; the arguments of a combination with respect to that lambda-list.
170 ;;; NODE-VAR the variable that holds the combination node.
171 ;;; ERROR-FORM is a form which is evaluated when the syntax of the
172 ;;; supplied arguments is incorrect or a non-constant argument keyword
173 ;;; is supplied. Defaults and other gunk are ignored. The second value
174 ;;; is a list of all the arguments bound, which the caller should make
175 ;;; IGNORABLE if their only purpose is to make the syntax work.
176 (defun parse-deftransform (lambda-list node-var error-form)
177 (multiple-value-bind (llks req opt rest keys) (parse-lambda-list lambda-list)
178 (let* ((tail (make-symbol "ARGS"))
179 (dummies (make-gensym-list 2))
180 (all-dummies (cons tail dummies))
181 (keyp (ll-kwds-keyp llks))
182 ;; FIXME: the logic for keywordicating a keyword arg specifier
183 ;; is repeated in a as many places as there are calls to
184 ;; parse-lambda-just, and more.
185 (keys (mapcar (lambda (spec)
186 (multiple-value-bind (key var)
187 (parse-key-arg-spec spec)
188 (cons var key)))
189 keys))
190 final-mandatory-arg)
191 (collect ((binds))
192 (binds `(,tail (basic-combination-args (truly-the basic-combination ,node-var))))
193 ;; The way this code checks for mandatory args is to verify that
194 ;; the last positional arg is not null (it should be an LVAR).
195 ;; But somebody could pedantically declare IGNORE on the last arg
196 ;; so bind a dummy for it and then bind from the dummy.
197 (mapl (lambda (args)
198 (cond ((cdr args)
199 (binds `(,(car args) (pop (truly-the list ,tail)))))
201 (setq final-mandatory-arg (pop dummies))
202 (binds `(,final-mandatory-arg (pop (truly-the list ,tail)))
203 `(,(car args) ,final-mandatory-arg)))))
204 req)
205 ;; Optionals are pretty easy.
206 (dolist (arg opt)
207 (binds `(,(if (atom arg) arg (car arg)) (pop (truly-the list ,tail)))))
208 ;; Now if min or max # of args is incorrect,
209 ;; or there are unacceptable keywords, bail out
210 (when (or req keyp (not rest))
211 (binds `(,(pop dummies) ; binding is for effect, not value
212 (unless (and ,@(if req `(,final-mandatory-arg))
213 ,@(if (and (not rest) (not keyp))
214 `((endp ,tail)))
215 ,@(if keyp
216 (if (ll-kwds-allowp llks)
217 `((check-key-args-constant ,tail))
218 `((check-transform-keys
219 ,tail ',(mapcar #'cdr keys))))))
220 ,error-form))))
221 (when rest
222 (binds `(,(car rest) ,tail)))
223 ;; Return list of bindings, the list of user-specified symbols,
224 ;; and the list of gensyms to be declared ignorable.
225 (values (append (binds)
226 (mapcar (lambda (k)
227 `(,(car k)
228 (find-keyword-lvar ,tail ',(cdr k))))
229 keys))
230 (sort (append (nset-difference (mapcar #'car (binds)) all-dummies)
231 (mapcar #'car keys))
232 #'string<)
233 (sort (intersection (mapcar #'car (binds)) (cdr all-dummies))
234 #'string<))))))
235 ) ; EVAL-WHEN
237 ;;;; DEFTRANSFORM
239 ;;; Define an IR1 transformation for NAME. An IR1 transformation
240 ;;; computes a lambda that replaces the function variable reference
241 ;;; for the call. A transform may pass (decide not to transform the
242 ;;; call) by calling the GIVE-UP-IR1-TRANSFORM function. LAMBDA-LIST
243 ;;; both determines how the current call is parsed and specifies the
244 ;;; LAMBDA-LIST for the resulting lambda.
246 ;;; We parse the call and bind each of the lambda-list variables to
247 ;;; the lvar which represents the value of the argument. When parsing
248 ;;; the call, we ignore the defaults, and always bind the variables
249 ;;; for unsupplied arguments to NIL. If a required argument is
250 ;;; missing, an unknown keyword is supplied, or an argument keyword is
251 ;;; not a constant, then the transform automatically passes. The
252 ;;; DECLARATIONS apply to the bindings made by DEFTRANSFORM at
253 ;;; transformation time, rather than to the variables of the resulting
254 ;;; lambda. Bound-but-not-referenced warnings are suppressed for the
255 ;;; lambda-list variables. The DOC-STRING is used when printing
256 ;;; efficiency notes about the defined transform.
258 ;;; Normally, the body evaluates to a form which becomes the body of
259 ;;; an automatically constructed lambda. We make LAMBDA-LIST the
260 ;;; lambda-list for the lambda, and automatically insert declarations
261 ;;; of the argument and result types. If the second value of the body
262 ;;; is non-null, then it is a list of declarations which are to be
263 ;;; inserted at the head of the lambda. Automatic lambda generation
264 ;;; may be inhibited by explicitly returning a lambda from the body.
266 ;;; The ARG-TYPES and RESULT-TYPE are used to create a function type
267 ;;; which the call must satisfy before transformation is attempted.
268 ;;; The function type specifier is constructed by wrapping (FUNCTION
269 ;;; ...) around these values, so the lack of a restriction may be
270 ;;; specified by omitting the argument or supplying *. The argument
271 ;;; syntax specified in the ARG-TYPES need not be the same as that in
272 ;;; the LAMBDA-LIST, but the transform will never happen if the
273 ;;; syntaxes can't be satisfied simultaneously. If there is an
274 ;;; existing transform for the same function that has the same type,
275 ;;; then it is replaced with the new definition.
277 ;;; These are the legal keyword options:
278 ;;; :RESULT - A variable which is bound to the result lvar.
279 ;;; :NODE - A variable which is bound to the combination node for the call.
280 ;;; :POLICY - A form which is supplied to the POLICY macro to determine
281 ;;; whether this transformation is appropriate. If the result
282 ;;; is false, then the transform automatically gives up.
283 ;;; :DEFUN-ONLY
284 ;;; - Don't actually instantiate a transform, instead just DEFUN
285 ;;; Name with the specified transform definition function. This
286 ;;; may be later instantiated with %DEFTRANSFORM.
287 ;;; - if the value is LAMBDA then returns a lambda form
288 ;;; instead of a defun.
290 ;;; :IMPORTANT
291 ;;; - If the transform fails and :IMPORTANT is
292 ;;; NIL, then never print an efficiency note.
293 ;;; :SLIGHTLY, then print a note if SPEED>INHIBIT-WARNINGS.
294 ;;; T, then print a note if SPEED>=INHIBIT-WARNINGS.
295 ;;; :SLIGHTLY is the default.
296 ;;; :VOP
297 ;;; - insert it at the front, stop other transforms from firing
298 ;;; if the function returns T.
299 (defmacro deftransform (name (lambda-list &optional (arg-types '*)
300 (result-type '*)
301 &key result policy node defun-only
302 (important :slightly)
303 vop)
304 &body body-decls-doc)
305 (declare (type (member nil :slightly t) important))
306 (when defun-only
307 (aver (eq important :slightly)) ; can't be specified
308 (aver (not policy))) ; has no effect on the defun
309 (multiple-value-bind (body decls doc) (parse-body body-decls-doc t)
310 (let ((n-node (or node '#:node))
311 (n-decls '#:decls)
312 (n-lambda '#:lambda))
313 (multiple-value-bind (bindings vars)
314 (parse-deftransform lambda-list n-node
315 '(give-up-ir1-transform))
316 (let ((stuff
317 `((,n-node &aux ,@bindings
318 ,@(when result
319 `((,result (node-lvar ,n-node)))))
320 (declare (ignorable ,@(mapcar #'car bindings)))
321 (declare (lambda-list (node)))
322 ,@decls
323 ,@(if doc `(,doc))
324 ;; What purpose does it serve to allow the transform's body
325 ;; to return decls as a second value? They would go in the
326 ;; right place if simply returned as part of the expression.
327 (block ,(fun-name-block-name name)
328 ,(if vop
329 `(throw 'give-up-ir1-transform
330 (values (if (progn ,@body)
331 :none
332 :failure)))
333 `(multiple-value-bind (,n-lambda ,n-decls)
334 (progn ,@body)
335 (if (and (consp ,n-lambda) (eq (car ,n-lambda) 'lambda))
336 ,n-lambda
337 `(lambda ,',lambda-list
338 (declare (ignorable ,@',vars))
339 ,@,n-decls
340 ,,n-lambda))))))))
341 (cond
342 ((not defun-only)
343 `(let ((fun (named-lambda (deftransform ,name) ,@stuff)))
344 ,@(loop for (types result-type) in (if (typep arg-types '(cons (eql :or)))
345 (cdr arg-types)
346 (list (list arg-types result-type)))
347 collect `(%deftransform ',name
348 ,(and policy `(lambda (,n-node) (policy ,n-node ,policy)))
349 '(function ,types ,result-type)
351 ,(if vop
352 :vop
353 important)))))
354 ((eq defun-only 'lambda)
355 `(named-lambda ,name ,@stuff))
356 (defun-only
357 `(defun ,name ,@stuff))))))))
359 (defmacro deftransforms (names (lambda-list &optional (arg-types '*)
360 (result-type '*)
361 &key result policy node (important :slightly))
362 &body body-decls-doc)
364 (let ((transform-name (symbolicate (car names) '-transform))
365 (type (list 'function arg-types result-type)))
366 `(progn
367 (deftransform ,transform-name
368 (,lambda-list ,arg-types ,result-type
369 :defun-only t
370 :result ,result :policy ,policy :node ,node)
371 ,@body-decls-doc)
372 (flet ,(if policy `((policy-test (node) (policy node ,policy))))
373 ,@(mapcar (lambda (name)
374 `(%deftransform ',name ,(if policy '#'policy-test) ',type
375 #',transform-name ,important))
376 names)))))
378 ;;; Create a function which parses combination args according to WHAT
379 ;;; and LAMBDA-LIST, where WHAT is either a function name or a list
380 ;;; (FUN-NAME KIND) and does some KIND of optimization.
382 ;;; The FUN-NAME must name a known function. LAMBDA-LIST is used
383 ;;; to parse the arguments to the combination as in DEFTRANSFORM. If
384 ;;; the argument syntax is invalid or there are non-constant keys,
385 ;;; then we simply return NIL.
387 ;;; The function is DEFUN'ed as FUNCTION-KIND-OPTIMIZER. Possible
388 ;;; kinds are DERIVE-TYPE, OPTIMIZER, LTN-ANNOTATE and IR2-CONVERT. If
389 ;;; a symbol is specified instead of a (FUNCTION KIND) list, then we
390 ;;; just do a DEFUN with the symbol as its name, and don't do anything
391 ;;; with the definition. This is useful for creating optimizers to be
392 ;;; passed by name to DEFKNOWN.
394 ;;; If supplied, NODE-VAR is bound to the combination node being
395 ;;; optimized. If additional VARS are supplied, then they are used as
396 ;;; the rest of the optimizer function's lambda-list. LTN-ANNOTATE
397 ;;; methods are passed an additional POLICY argument, and IR2-CONVERT
398 ;;; methods are passed an additional IR2-BLOCK argument.
399 (defmacro defoptimizer (what (lambda-list
400 &optional (node (gensym))
401 &rest vars)
402 &body body)
403 (let ((name (flet ((function-name (name)
404 (etypecase name
405 (symbol name)
406 ((cons (eql setf) (cons symbol null))
407 (symbolicate (car name) "-" (cadr name))))))
408 (if (symbolp what)
409 what
410 (symbolicate (function-name (first what))
412 (if (consp (second what))
413 (caadr what)
414 (second what))
415 "-OPTIMIZER")))))
416 (if (typep what '(cons (eql vop-optimize)))
417 `(progn
418 (defun ,name (,lambda-list)
419 ,@body)
420 ,@(loop for vop-name in (ensure-list (second what))
421 collect
422 `(set-vop-optimizer (template-or-lose ',vop-name)
423 ,(if (cddr what)
424 `(cons #',name ',(caddr what))
425 `#',name))))
426 (binding* (((forms decls) (parse-body body nil))
427 ((var-decls more-decls) (extract-var-decls decls vars))
428 ((binds lambda-vars)
429 (parse-deftransform lambda-list node
430 `(return-from ,name
431 ,(if (and (consp what)
432 (eq (second what)
433 'equality-constraint))
434 :give-up
435 nil))))
436 (args (gensym)))
437 (declare (ignore lambda-vars))
438 `(progn
439 ;; We can't stuff the BINDS as &AUX vars into the lambda list
440 ;; because there can be a RETURN-FROM in there.
441 (defun ,name (,node ,@vars &rest ,args)
442 (declare (ignorable ,node ,@(butlast vars))
443 (ignore ,args))
444 ,@(if var-decls (list var-decls))
445 (let* (,@binds)
446 (declare (ignorable ,@(mapcar #'car binds)))
447 ,@more-decls ,@forms))
448 ,@(when (consp what)
449 `((setf (,(let ((*package* (sb-xc:symbol-package 'fun-info)))
450 (symbolicate "FUN-INFO-" (second what)))
451 (fun-info-or-lose ',(first what)))
452 #',name))))))))
454 (defmacro defoptimizers (kind names (lambda-list
455 &optional (node (gensym))
456 &rest vars)
457 &body body)
458 (let ((optimizer-name (symbolicate (car names)
460 kind
461 "-OPTIMIZER")))
462 `(progn
463 (defoptimizer ,optimizer-name
464 (,lambda-list ,node ,@vars)
465 ,@body)
466 ,@(loop for name in names
467 collect `(setf (,(let ((*package* (sb-xc:symbol-package 'fun-info)))
468 (symbolicate "FUN-INFO-" kind))
469 (fun-info-or-lose ',name))
470 #',optimizer-name)))))
472 ;;;; IR groveling macros
474 ;;; Iterate over the blocks in a component, binding BLOCK-VAR to each
475 ;;; block in turn. The value of ENDS determines whether to iterate
476 ;;; over dummy head and tail blocks:
477 ;;; NIL -- Skip Head and Tail (the default)
478 ;;; :HEAD -- Do head but skip tail
479 ;;; :TAIL -- Do tail but skip head
480 ;;; :BOTH -- Do both head and tail
482 ;;; If supplied, RESULT-FORM is the value to return.
483 (defmacro do-blocks ((block-var component &optional ends result) &body body)
484 (unless (member ends '(nil :head :tail :both))
485 (error "losing ENDS value: ~S" ends))
486 (let ((n-component (gensym))
487 (n-tail (gensym)))
488 `(let* ((,n-component ,component)
489 (,n-tail ,(if (member ends '(:both :tail))
491 `(component-tail ,n-component))))
492 (do ((,block-var ,(if (member ends '(:both :head))
493 `(component-head ,n-component)
494 `(block-next (component-head ,n-component)))
495 (block-next ,block-var)))
496 ((eq ,block-var ,n-tail) ,result)
497 ,@body))))
498 ;;; like DO-BLOCKS, only iterating over the blocks in reverse order
499 (defmacro do-blocks-backwards ((block-var component &optional ends result) &body body)
500 (unless (member ends '(nil :head :tail :both))
501 (error "losing ENDS value: ~S" ends))
502 (let ((n-component (gensym))
503 (n-head (gensym)))
504 `(let* ((,n-component ,component)
505 (,n-head ,(if (member ends '(:both :head))
507 `(component-head ,n-component))))
508 (do ((,block-var ,(if (member ends '(:both :tail))
509 `(component-tail ,n-component)
510 `(block-prev (component-tail ,n-component)))
511 (block-prev ,block-var)))
512 ((eq ,block-var ,n-head) ,result)
513 ,@body))))
515 ;;; Iterate over the uses of LVAR, binding NODE to each one
516 ;;; successively.
517 (defmacro do-uses ((node-var lvar &optional result) &body body)
518 (with-unique-names (uses)
519 `(let ((,uses (lvar-uses ,lvar)))
520 (block nil
521 (flet ((do-1-use (,node-var)
522 ,@body))
523 (if (listp ,uses)
524 (dolist (node ,uses)
525 (do-1-use node))
526 (do-1-use ,uses)))
527 ,result))))
529 ;;; Iterate over the nodes in BLOCK, binding NODE-VAR to the each node
530 ;;; and LVAR-VAR to the node's LVAR. The only keyword option is
531 ;;; RESTART-P, which causes iteration to be restarted when a node is
532 ;;; deleted out from under us. (If not supplied, this is an error.)
534 ;;; In the forward case, we terminate when NODE does not have NEXT, so
535 ;;; that we do not have to worry about our termination condition being
536 ;;; changed when new code is added during the iteration. In the
537 ;;; backward case, we do NODE-PREV before evaluating the body so that
538 ;;; we can keep going when the current node is deleted.
540 ;;; When RESTART-P is supplied to DO-NODES, we start iterating over
541 ;;; again at the beginning of the block when we run into a ctran whose
542 ;;; block differs from the one we are trying to iterate over, either
543 ;;; because the block was split, or because a node was deleted out
544 ;;; from under us (hence its block is NIL.) If the block start is
545 ;;; deleted, we just punt. With RESTART-P, we are also more careful
546 ;;; about termination, re-indirecting the BLOCK-LAST each time.
547 (defmacro do-nodes ((node-var lvar-var block &key restart-p)
548 &body body)
549 (with-unique-names (n-block n-start)
550 `(do* ((,n-block ,block)
551 (,n-start (block-start ,n-block))
553 (,node-var (ctran-next ,n-start)
554 ,(if restart-p
555 `(let ((next (node-next ,node-var)))
556 (cond
557 ((not next)
558 (return))
559 ((eq (ctran-block next) ,n-block)
560 (ctran-next next))
562 (let ((start (block-start ,n-block)))
563 (unless (eq (ctran-kind start)
564 :block-start)
565 (return nil))
566 (ctran-next start)))))
567 `(acond ((node-next ,node-var)
568 (ctran-next it))
569 (t (return)))))
570 ,@(when lvar-var
571 `((,lvar-var (when (valued-node-p ,node-var)
572 (node-lvar ,node-var))
573 (when (valued-node-p ,node-var)
574 (node-lvar ,node-var))))))
575 (nil)
576 ,@body
577 ,@(when restart-p
578 `((when (block-delete-p ,n-block)
579 (return)))))))
581 ;;; Like DO-NODES, only iterating in reverse order. Should be careful
582 ;;; with block being split under us.
583 (defmacro do-nodes-backwards ((node-var lvar block &key restart-p) &body body)
584 (let ((n-block (gensym))
585 (n-prev (gensym)))
586 `(loop with ,n-block = ,block
587 for ,node-var = (block-last ,n-block) then
588 ,(if restart-p
589 `(if (eq ,n-block (ctran-block ,n-prev))
590 (ctran-use ,n-prev)
591 (block-last ,n-block))
592 `(ctran-use ,n-prev))
593 for ,n-prev = (when ,node-var (node-prev ,node-var))
594 and ,lvar = (when (and ,node-var (valued-node-p ,node-var))
595 (node-lvar ,node-var))
596 while ,(if restart-p
597 `(and ,node-var (not (block-to-be-deleted-p ,n-block)))
598 node-var)
599 do (progn
600 ,@body))))
602 (defmacro do-nodes-carefully ((node-var block) &body body)
603 (with-unique-names (n-block n-ctran)
604 `(loop with ,n-block = ,block
605 for ,n-ctran = (block-start ,n-block) then (node-next ,node-var)
606 for ,node-var = (and ,n-ctran (ctran-next ,n-ctran))
607 while ,node-var
608 do (progn ,@body))))
610 (defmacro do-nested-cleanups ((cleanup-var block &optional return-value)
611 &body body)
612 `(block nil
613 (map-nested-cleanups
614 (lambda (,cleanup-var) ,@body) ,block ,return-value)))
616 ;;; Bind the IR1 context variables to the values associated with NODE,
617 ;;; so that IR1 conversion can be done after the main conversion pass
618 ;;; has finished.
619 (defmacro with-ir1-environment-from-node (node &rest forms)
620 (once-only ((node node))
621 `(let ((*current-component* (node-component ,node))
622 (*lexenv* (node-lexenv ,node))
623 (*current-path* (node-source-path ,node)))
624 (aver-live-component *current-component*)
625 ,@forms)))
627 ;;; *SOURCE-PATHS* is a hashtable from source code forms to the path
628 ;;; taken through the source to reach the form. This provides a way to
629 ;;; keep track of the location of original source forms, even when
630 ;;; macroexpansions and other arbitary permutations of the code
631 ;;; happen. This table is initialized by calling FIND-SOURCE-PATHS on
632 ;;; the original source.
634 ;;; It is fairly useless to store symbols, characters, or fixnums in
635 ;;; this table, as 42 is EQ to 42 no matter where in the source it
636 ;;; appears. GET-SOURCE-PATH and NOTE-SOURCE-PATH functions should be
637 ;;; always used to access this table.
638 (declaim (type hash-table *source-paths*))
639 (defvar *source-paths*)
641 (defmacro with-source-paths (&body forms)
642 `(let ((*source-paths* (make-hash-table :test 'eq)))
643 ,@forms))
645 ;;; Bind the hashtables used for keeping track of global variables,
646 ;;; functions, etc.
647 (defmacro with-ir1-namespace (&body forms)
648 `(let ((*ir1-namespace* (make-ir1-namespace)))
649 ,@forms))
651 ;;; Look up NAME in the lexical environment namespace designated by
652 ;;; SLOT, returning the <value, T>, or <NIL, NIL> if no entry. The
653 ;;; :TEST keyword may be used to determine the name equality
654 ;;; predicate.
655 (defmacro lexenv-find (name slot &key (lexenv '*lexenv*) test
656 &aux (accessor (package-symbolicate
657 (cl:symbol-package 'lexenv-funs)
658 "LEXENV-" slot)))
659 (once-only ((n-res `(assoc ,name (,accessor ,lexenv) :test ,(or test '#'eq))))
660 `(if ,n-res
661 (values (cdr ,n-res) t)
662 (values nil nil))))
664 (defmacro with-component-last-block ((component block) &body body)
665 (with-unique-names (old-last-block)
666 (once-only ((component component)
667 (block block))
668 `(let ((,old-last-block (component-last-block ,component)))
669 (unwind-protect
670 (progn (setf (component-last-block ,component)
671 ,block)
672 ,@body)
673 (setf (component-last-block ,component)
674 ,old-last-block))))))
677 ;;;; boolean attribute utilities
678 ;;;;
679 ;;;; We need to maintain various sets of boolean attributes for known
680 ;;;; functions and VOPs. To save space and allow for quick set
681 ;;;; operations, we represent the attributes as bits in a fixnum.
683 (deftype attributes () 'fixnum)
685 ;;; Given a list of attribute names and an alist that translates them
686 ;;; to masks, return the OR of the masks.
687 (defun encode-attribute-mask (names universe)
688 (loop for name in names
689 for pos = (position name universe)
690 sum (if pos (ash 1 pos) (error "unknown attribute name: ~S" name))))
692 (defun decode-attribute-mask (bits universe)
693 (loop for name across universe
694 for mask = 1 then (ash mask 1)
695 when (logtest mask bits) collect name))
697 ;;; Define a new class of boolean attributes, with the attributes
698 ;;; having the specified ATTRIBUTE-NAMES. NAME is the name of the
699 ;;; class, which is used to generate some macros to manipulate sets of
700 ;;; the attributes:
702 ;;; NAME-attributep attributes attribute-name*
703 ;;; Return true if one of the named attributes is present, false
704 ;;; otherwise. When set with SETF, updates the place Attributes
705 ;;; setting or clearing the specified attributes.
707 ;;; NAME-attributes attribute-name*
708 ;;; Return a set of the named attributes.
709 (defmacro !def-boolean-attribute (name &body attribute-names)
710 (let ((vector (coerce attribute-names 'vector))
711 (constructor (symbolicate name "-ATTRIBUTES"))
712 (test-name (symbolicate name "-ATTRIBUTEP")))
713 `(eval-when (:compile-toplevel :load-toplevel :execute)
714 (defmacro ,constructor (&rest attribute-names)
715 "Automagically generated boolean attribute creation function.
716 See !DEF-BOOLEAN-ATTRIBUTE."
717 (encode-attribute-mask attribute-names ,vector))
718 (defun ,(symbolicate "DECODE-" name "-ATTRIBUTES") (attributes)
719 (decode-attribute-mask attributes ,vector))
720 (defmacro ,test-name (attributes &rest attribute-names)
721 "Automagically generated boolean attribute test function.
722 See !DEF-BOOLEAN-ATTRIBUTE."
723 `(logtest (the attributes ,attributes)
724 (,',constructor ,@attribute-names)))
725 (define-setf-expander ,test-name (place &rest attributes
726 &environment env)
727 "Automagically generated boolean attribute setter. See
728 !DEF-BOOLEAN-ATTRIBUTE."
729 (multiple-value-bind (temps values stores setter getter)
730 (#+sb-xc-host cl:get-setf-expansion
731 #-sb-xc-host get-setf-expansion place env)
732 (when (cdr stores)
733 (error "multiple store variables for ~S" place))
734 (let ((newval (gensym))
735 (n-place (gensym))
736 (mask (encode-attribute-mask attributes ,vector)))
737 (values `(,@temps ,n-place)
738 `(,@values ,getter)
739 `(,newval)
740 `(let ((,(first stores)
741 (if ,newval
742 (logior ,n-place ,mask)
743 (logandc2 ,n-place ,mask))))
744 ,setter
745 ,newval)
746 `(,',test-name ,n-place ,@attributes))))))))
748 ;;; And now for some gratuitous pseudo-abstraction...
750 ;;; ATTRIBUTES-UNION
751 ;;; Return the union of all the sets of boolean attributes which are its
752 ;;; arguments.
753 ;;; ATTRIBUTES-INTERSECTION
754 ;;; Return the intersection of all the sets of boolean attributes which
755 ;;; are its arguments.
756 ;;; ATTRIBUTES=
757 ;;; True if the attributes present in ATTR1 are identical to
758 ;;; those in ATTR2.
759 (defmacro attributes-union (&rest attributes)
760 `(the attributes
761 (logior ,@(mapcar (lambda (x) `(the attributes ,x)) attributes))))
762 (defmacro attributes-intersection (&rest attributes)
763 `(the attributes
764 (logand ,@(mapcar (lambda (x) `(the attributes ,x)) attributes))))
765 (declaim (ftype (function (attributes attributes) boolean) attributes=))
766 (declaim (inline attributes=))
767 (defun attributes= (attr1 attr2)
768 (eql attr1 attr2))
771 ;;;; the EVENT statistics/trace utility
773 ;;; FIXME: This seems to be useful for troubleshooting and
774 ;;; experimentation, not for ordinary use, so it should probably
775 ;;; become conditional on SB-SHOW.
777 (defstruct (event-info (:copier nil))
778 ;; The name of this event.
779 (name (missing-arg) :type symbol)
780 ;; The string rescribing this event.
781 (description (missing-arg) :type string)
782 ;; The name of the variable we stash this in.
783 (var (missing-arg) :type symbol)
784 ;; The number of times this event has happened.
785 (count 0 :type fixnum)
786 ;; The level of significance of this event.
787 (level (missing-arg) :type unsigned-byte)
788 ;; If true, a function that gets called with the node that the event
789 ;; happened to.
790 (action nil :type (or function null)))
791 (declaim (freeze-type event-info))
793 ;;; A hashtable from event names to event-info structures.
794 (define-load-time-global *event-info* (make-hash-table :test 'eq))
796 ;;; Return the event info for Name or die trying.
797 (declaim (ftype (function (t) event-info) event-info-or-lose))
798 (defun event-info-or-lose (name)
799 (let ((res (gethash name *event-info*)))
800 (unless res
801 (error "~S is not the name of an event." name))
802 res))
804 ;;; Return the number of times that EVENT has happened.
805 (declaim (ftype (function (symbol) fixnum) event-count))
806 (defun event-count (name)
807 (event-info-count (event-info-or-lose name)))
809 ;;; Return the function that is called when Event happens. If this is
810 ;;; null, there is no action. The function is passed the node to which
811 ;;; the event happened, or NIL if there is no relevant node. This may
812 ;;; be set with SETF.
813 (declaim (ftype (function (symbol) (or function null)) event-action))
814 (defun event-action (name)
815 (event-info-action (event-info-or-lose name)))
816 (declaim (ftype (function (symbol (or function null)) (or function null))
817 %set-event-action))
818 (defun %set-event-action (name new-value)
819 (setf (event-info-action (event-info-or-lose name))
820 new-value))
821 (defsetf event-action %set-event-action)
823 ;;; Return the non-negative integer which represents the level of
824 ;;; significance of the event Name. This is used to determine whether
825 ;;; to print a message when the event happens. This may be set with
826 ;;; SETF.
827 (declaim (ftype (function (symbol) unsigned-byte) event-level))
828 (defun event-level (name)
829 (event-info-level (event-info-or-lose name)))
830 (declaim (ftype (function (symbol unsigned-byte) unsigned-byte) %set-event-level))
831 (defun %set-event-level (name new-value)
832 (setf (event-info-level (event-info-or-lose name))
833 new-value))
834 (defsetf event-level %set-event-level)
836 ;;; Define a new kind of event. NAME is a symbol which names the event
837 ;;; and DESCRIPTION is a string which describes the event. Level
838 ;;; (default 0) is the level of significance associated with this
839 ;;; event; it is used to determine whether to print a Note when the
840 ;;; event happens.
841 (defmacro defevent (name description &optional (level 0))
842 (let ((var-name (symbolicate "*" name "-EVENT-INFO*")))
843 `(progn
844 (defglobal ,var-name
845 (make-event-info :name ',name
846 :description ',description
847 :var ',var-name
848 :level ,level))
849 (eval-when (:compile-toplevel :load-toplevel :execute)
850 (setf (gethash ',name *event-info*) ,var-name))
851 ',name)))
853 ;;; the lowest level of event that will print a note when it occurs
854 (declaim (type unsigned-byte *event-note-threshold*))
855 (defvar *event-note-threshold* 1)
857 ;;; Note that the event with the specified NAME has happened. NODE is
858 ;;; evaluated to determine the node to which the event happened.
859 (defmacro event (name &optional node)
860 ;; Increment the counter and do any action. Mumble about the event if
861 ;; policy indicates.
862 `(%event ,(event-info-var (event-info-or-lose name)) ,node))
864 ;;; Print a listing of events and their counts, sorted by the count.
865 ;;; Events that happened fewer than Min-Count times will not be
866 ;;; printed. Stream is the stream to write to.
867 (declaim (ftype (function (&optional unsigned-byte stream) (values)) event-statistics))
868 (defun event-statistics (&optional (min-count 1) (stream *standard-output*))
869 (collect ((info))
870 (maphash (lambda (k v)
871 (declare (ignore k))
872 (when (>= (event-info-count v) min-count)
873 (info v)))
874 *event-info*)
875 (dolist (event (sort (info) #'> :key #'event-info-count))
876 (format stream "~6D: ~A~%" (event-info-count event)
877 (event-info-description event)))
878 (values))
879 (values))
881 (declaim (ftype (function nil (values)) clear-event-statistics))
882 (defun clear-event-statistics ()
883 (maphash (lambda (k v)
884 (declare (ignore k))
885 (setf (event-info-count v) 0))
886 *event-info*)
887 (values))
889 ;;;; functions on directly-linked lists (linked through specialized
890 ;;;; NEXT operations)
892 (declaim (inline find-in position-in))
894 ;;; Find ELEMENT in a null-terminated LIST linked by the accessor
895 ;;; function NEXT. KEY and TEST are the same as for generic sequence functions.
896 (defun find-in (next
897 element
898 list
899 &key
900 (key #'identity)
901 (test #'eql))
902 (declare (type function next key test))
903 (declare (dynamic-extent next key test))
904 (do ((current list (funcall next current)))
905 ((null current) nil)
906 (when (funcall test (funcall key current) element)
907 (return current))))
909 ;;; Return the position of ELEMENT (or NIL if absent) in a
910 ;;; null-terminated LIST linked by the accessor function NEXT.
911 ;;; KEY and TEST are the same as for generic sequence functions.
912 (defun position-in (next
913 element
914 list
915 &key
916 (key #'identity)
917 (test #'eql))
918 (declare (type function next key test))
919 (declare (dynamic-extent next key test))
920 (do ((current list (funcall next current))
921 (i 0 (1+ i)))
922 ((null current) nil)
923 (when (funcall test (funcall key current) element)
924 (return i))))
926 (defmacro deletef-in (next place item &environment env)
927 (multiple-value-bind (temps vals stores store access)
928 (#-sb-xc-host get-setf-expansion #+sb-xc-host cl:get-setf-expansion place env)
929 (when (cdr stores)
930 (error "multiple store variables for ~S" place))
931 (let ((n-item (gensym))
932 (n-place (gensym))
933 (n-current (gensym))
934 (n-prev (gensym)))
935 `(let* (,@(mapcar #'list temps vals)
936 (,n-place ,access)
937 (,n-item ,item))
938 (if (eq ,n-place ,n-item)
939 (let ((,(first stores) (,next ,n-place)))
940 ,store)
941 (do ((,n-prev ,n-place ,n-current)
942 (,n-current (,next ,n-place)
943 (,next ,n-current)))
944 ((eq ,n-current ,n-item)
945 (setf (,next ,n-prev)
946 (,next ,n-current)))))
947 (values)))))
949 ;;; Push ITEM onto a list linked by the accessor function NEXT that is
950 ;;; stored in PLACE.
952 (defmacro push-in (next item place &environment env)
953 (multiple-value-bind (temps vals stores store access)
954 (#-sb-xc-host get-setf-expansion #+sb-xc-host cl:get-setf-expansion place env)
955 (when (cdr stores)
956 (error "multiple store variables for ~S" place))
957 `(let (,@(mapcar #'list temps vals)
958 (,(first stores) ,item))
959 (setf (,next ,(first stores)) ,access)
960 ,store
961 (values))))
963 (defmacro position-or-lose (&rest args)
964 `(or (position ,@args)
965 (error "shouldn't happen?")))
967 ;;; user-definable compiler io syntax
969 ;;; We use WITH-SANE-IO-SYNTAX to provide safe defaults, and provide
970 ;;; *COMPILER-PRINT-VARIABLE-ALIST* for user customization.
971 (defvar *compiler-print-variable-alist* nil
972 "an association list describing new bindings for special variables
973 to be used by the compiler for error-reporting, etc. Eg.
975 ((*PRINT-LENGTH* . 10) (*PRINT-LEVEL* . 6) (*PRINT-PRETTY* . NIL))
977 The variables in the CAR positions are bound to the values in the CDR
978 during the execution of some debug commands. When evaluating arbitrary
979 expressions in the debugger, the normal values of the printer control
980 variables are in effect.
982 Initially empty, *COMPILER-PRINT-VARIABLE-ALIST* is Typically used to
983 specify bindings for printer control variables.")
985 (defmacro with-compiler-io-syntax (&body forms)
986 `(with-sane-io-syntax
987 (progv
988 (nreverse (mapcar #'car *compiler-print-variable-alist*))
989 (nreverse (mapcar #'cdr *compiler-print-variable-alist*))
990 ,@forms)))