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