Fix cross build.
[sbcl.git] / src / code / macros.lisp
blobbf1e71311d95daef4f381accea7dd36e6761c5e7
1 ;;;; lots of basic macros for the target SBCL
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-IMPL")
15 ;;;; DEFMACRO
17 ;;; Inform the cross-compiler how to expand SB-XC:DEFMACRO (= DEFMACRO)
18 ;;; and supporting macros using the already defined host macros until
19 ;;; this file is itself cross-compiled.
20 #+sb-xc-host
21 (flet ((defmacro-using-host-expander (name)
22 (setf (macro-function name)
23 (lambda (form env)
24 (declare (ignore env))
25 ;; Since SB-KERNEL:LEXENV isn't compatible with the host,
26 ;; just pass NIL. The expansion correctly captures a non-null
27 ;; environment, but the expander doesn't need it.
28 (funcall (cl:macro-function name) form nil)))))
29 (defmacro-using-host-expander 'sb-xc:defmacro)
30 (defmacro-using-host-expander 'named-ds-bind)
31 (defmacro-using-host-expander 'binding*)
32 (defmacro-using-host-expander 'sb-xc:deftype)
33 ;; FIXME: POLICY doesn't support DEFMACRO, but we need it ASAP.
34 (defmacro-using-host-expander 'sb-c:policy))
37 ;;;; Destructuring-bind
39 (sb-xc:defmacro destructuring-bind (lambda-list expression &body body
40 &environment env)
41 (declare (ignore env)) ; could be policy-sensitive (but isn't)
42 "Bind the variables in LAMBDA-LIST to the corresponding values in the
43 tree structure resulting from the evaluation of EXPRESSION."
44 `(binding* ,(sb-c::expand-ds-bind lambda-list expression t nil)
45 ,@body))
48 ;;;; DEFUN
50 ;;; Should we save the inline expansion of the function named NAME?
51 (defun save-inline-expansion-p (name)
52 (or
53 ;; the normal reason for saving the inline expansion
54 (let ((inlinep (info :function :inlinep name)))
55 (member inlinep '(inline maybe-inline)))
56 ;; another reason for saving the inline expansion: If the
57 ;; ANSI-recommended idiom
58 ;; (DECLAIM (INLINE FOO))
59 ;; (DEFUN FOO ..)
60 ;; (DECLAIM (NOTINLINE FOO))
61 ;; has been used, and then we later do another
62 ;; (DEFUN FOO ..)
63 ;; without a preceding
64 ;; (DECLAIM (INLINE FOO))
65 ;; what should we do with the old inline expansion when we see the
66 ;; new DEFUN? Overwriting it with the new definition seems like
67 ;; the only unsurprising choice.
68 (nth-value 1 (fun-name-inline-expansion name))))
70 (defun extract-dx-args (lambda-list decl-forms)
71 (let (dx-decls)
72 (dolist (form decl-forms)
73 (dolist (expr (cdr form))
74 (when (typep expr '(cons (eql dynamic-extent)))
75 (setf dx-decls (union dx-decls (cdr expr))))))
76 (unless dx-decls
77 (return-from extract-dx-args nil))
78 ;; TODO: in addition to ":SILENT T" supressing warnings, PARSE-LAMBDA-LIST
79 ;; needs to allow :CONDITION-CLASS = NIL to ask that no errors be signaled.
80 ;; An indicator can be returned so that at worst the code below does nothing.
81 (multiple-value-bind (llks required optional rest key aux)
82 (parse-lambda-list lambda-list :silent t)
83 (declare (ignore llks rest))
84 ;; We enforce uniqueness of the symbols in the union of REQUIRED,
85 ;; OPTIONAL, REST, KEY (including any supplied-p variables),
86 ;; but there may be an AUX binding shadowing a lambda binding.
87 ;; This affects something like:
88 ;; (LAMBDA (X &AUX (X (MAKE-FOO X))) (DECLARE (DYNAMIC-EXTENT X))
89 ;; in which the decl does not pertain to argument X.
90 (let ((arg-index 0) caller-dxable)
91 (labels ((examine (sym dx-note)
92 (when (and (member sym dx-decls) (not (shadowed-p sym)))
93 (push dx-note caller-dxable))
94 (incf arg-index))
95 (shadowed-p (sym)
96 (dolist (binding aux)
97 (when (eq (if (listp binding) (car binding) binding) sym)
98 (return t)))))
99 (dolist (spec required)
100 (examine spec arg-index))
101 (dolist (spec optional)
102 (examine (if (listp spec) (car spec) spec) arg-index))
103 (dolist (spec key)
104 (multiple-value-bind (keyword var) (parse-key-arg-spec spec)
105 (examine var keyword))))
106 (nreverse caller-dxable)))))
108 (defun block-compilation-non-entry-point (name)
109 (and (boundp 'sb-c:*compilation*)
110 (let* ((compilation sb-c:*compilation*)
111 (entry-points (sb-c::entry-points compilation)))
112 (and (sb-c::block-compile compilation)
113 entry-points
114 (not (member name entry-points :test #'equal))))))
116 (flet ((defun-expander (env name lambda-list body snippet &optional source-form)
117 (multiple-value-bind (forms decls doc) (parse-body body t)
118 ;; Maybe kill docstring, but only under the cross-compiler.
119 #+(and (not sb-doc) sb-xc-host) (setq doc nil)
120 (let* (;; stuff shared between LAMBDA and INLINE-LAMBDA and NAMED-LAMBDA
121 (lambda-guts `(,@decls (block ,(fun-name-block-name name) ,@forms)))
122 (lambda `(lambda ,lambda-list ,@lambda-guts))
123 (named-lambda `(named-lambda ,name ,lambda-list
124 ,@(when *top-level-form-p* '((declare (sb-c::top-level-form))))
125 ,@(when doc (list doc)) ,@lambda-guts))
126 ;; DXABLE-ARGS and SNIPPET are mutually exclusive, so we can sleazily pass
127 ;; whichever exists (if either does) as one parameter to %DEFUN.
128 (extra-info (or snippet (extract-dx-args lambda-list decls)))
129 (inline-thing
130 (cond ((member snippet '(:predicate :copier :accessor)) nil)
131 ;; If the defstruct snippet is :CONSTRUCTOR, we might have to store
132 ;; a full inline expansion depending on the lexical environment.
133 ((save-inline-expansion-p name)
134 ;; we want to attempt to inline, so complain if we can't
135 (cond ((sb-c:inline-syntactic-closure-lambda lambda env))
137 (#+sb-xc-host warn
138 #-sb-xc-host sb-c:maybe-compiler-notify
139 "lexical environment too hairy, can't inline DEFUN ~S"
140 name)
141 nil))))))
142 (when (and (eq snippet :constructor)
143 (not (typep inline-thing '(cons (eql sb-c:lambda-with-lexenv)))))
144 ;; constructor in null lexenv need not save the expansion
145 (setq inline-thing nil))
146 (when inline-thing
147 (setq inline-thing (list 'quote inline-thing)))
148 (when (and extra-info (not (keywordp extra-info)))
149 (setq extra-info (list 'quote extra-info)))
150 (let ((definition
151 (if (block-compilation-non-entry-point name)
152 `(progn
153 (sb-c::%refless-defun ,named-lambda)
154 ',name)
155 `(%defun ',name ,named-lambda
156 ,@(when (or inline-thing extra-info) `(,inline-thing))
157 ,@(when extra-info `(,extra-info))))))
158 `(progn
159 (eval-when (:compile-toplevel)
160 (sb-c:%compiler-defun ',name t ,inline-thing ,extra-info))
161 ,(if source-form
162 `(sb-c::with-source-form ,source-form ,definition)
163 definition)
164 ;; This warning, if produced, comes after the DEFUN happens.
165 ;; When compiling, there's no real difference, but when interpreting,
166 ;; if there is a handler for style-warning that nonlocally exits,
167 ;; it's wrong to have skipped the DEFUN itself, since if there is no
168 ;; function, then the warning ought not to have been issued at all.
169 ,@(when (typep name '(cons (eql setf)))
170 `((eval-when (:compile-toplevel :execute)
171 (sb-c::warn-if-setf-macro ',name))
172 ',name))))))))
174 ;;; This is one of the major places where the semantics of block
175 ;;; compilation is handled. Substitution for global names is totally
176 ;;; inhibited if (block-compile *compilation*) is NIL. And if
177 ;;; (block-compile *compilation*) is true and entry points are
178 ;;; specified, then we don't install global definitions for non-entry
179 ;;; functions (effectively turning them into local lexical functions.)
180 (sb-xc:defmacro defun (&environment env name lambda-list &body body)
181 "Define a function at top level."
182 (check-designator name 'defun #'legal-fun-name-p "function name")
183 #+sb-xc-host
184 (unless (cl:symbol-package (fun-name-block-name name))
185 (warn "DEFUN of uninterned function name ~S (tricky for GENESIS)" name))
186 (defun-expander env name lambda-list body nil))
188 ;; extended defun as used by defstruct
189 (sb-xc:defmacro sb-c:xdefun (&environment env name snippet source-form lambda-list &body body)
190 (defun-expander env name lambda-list body snippet source-form)))
192 ;;;; DEFCONSTANT, DEFVAR and DEFPARAMETER
194 (sb-xc:defmacro defconstant (name value &optional (doc nil docp))
195 "Define a global constant, saying that the value is constant and may be
196 compiled into code. If the variable already has a value, and this is not
197 EQL to the new value, the code is not portable (undefined behavior). The
198 third argument is an optional documentation string for the variable."
199 (check-designator name 'defconstant)
200 `(eval-when (:compile-toplevel :load-toplevel :execute)
201 (%defconstant ',name ,value (sb-c:source-location)
202 ,@(and docp `(',doc)))))
205 (declaim (ftype (sfunction (symbol t &optional t t) null)
206 about-to-modify-symbol-value))
207 ;;; the guts of DEFCONSTANT
208 (defun %defconstant (name value source-location &optional (doc nil docp))
209 #+sb-xc-host (declare (ignore doc docp))
210 (unless (symbolp name)
211 (error "The constant name is not a symbol: ~S" name))
212 (with-single-package-locked-error (:symbol name
213 "defining ~s as a constant")
214 (when (looks-like-name-of-special-var-p name)
215 (style-warn 'asterisks-around-constant-variable-name
216 :format-control "Defining ~S as a constant"
217 :format-arguments (list name)))
218 (when source-location
219 (setf (info :source-location :constant name) source-location))
220 (let ((kind (info :variable :kind name)))
221 (case kind
222 (:constant
223 ;; Note: This behavior (discouraging any non-EQL modification)
224 ;; is unpopular, but it is specified by ANSI (i.e. ANSI says a
225 ;; non-EQL change has undefined consequences). If people really
226 ;; want bindings which are constant in some sense other than
227 ;; EQL, I suggest either just using DEFVAR (which is usually
228 ;; appropriate, despite the un-mnemonic name), or defining
229 ;; something like the DEFCONSTANT-EQX macro used in SBCL (which
230 ;; is occasionally more appropriate). -- WHN 2001-12-21
231 (if (boundp name)
232 (if (typep name '(or boolean keyword))
233 ;; Non-continuable error.
234 (about-to-modify-symbol-value name 'defconstant)
235 (let ((old (symbol-value name)))
236 (unless (or (eql value old)
237 ;; SAPs behave like numbers but yet EQL doesn't work on them,
238 ;; special case it.
239 ;; Nobody will notices that the constant
240 ;; is not EQ, since it can be copied at
241 ;; any time anyway.
242 #-sb-xc-host
243 (and (system-area-pointer-p old)
244 (system-area-pointer-p value)
245 (sap= old value)))
246 (multiple-value-bind (ignore aborted)
247 (with-simple-restart (abort "Keep the old value.")
248 (cerror "Go ahead and change the value."
249 'defconstant-uneql
250 :name name
251 :old-value old
252 :new-value value))
253 (declare (ignore ignore))
254 (when aborted
255 (return-from %defconstant name))))))
256 (warn "redefining a MAKUNBOUND constant: ~S" name)))
257 (:unknown
258 ;; (This is OK -- undefined variables are of this kind. So we
259 ;; don't warn or error or anything, just fall through.)
261 (t (warn "redefining ~(~A~) ~S to be a constant" kind name)))))
262 (dolist (backpatch (info :variable :forward-references name))
263 (funcall backpatch value))
264 (clear-info :variable :forward-references name)
265 ;; We ought to be consistent in treating any change of :VARIABLE :KIND
266 ;; as a continuable error. The above CASE expression pre-dates the
267 ;; existence of symbol-macros (I believe), but at a bare minimum,
268 ;; INFO should return NIL for its second value if requesting the
269 ;; :macro-expansion of something that is getting defined as constant.
270 (clear-info :variable :macro-expansion name)
271 (clear-info :source-location :symbol-macro name)
272 #-sb-xc-host
273 (progn
274 (when docp
275 (setf (documentation name 'variable) doc))
276 (%set-symbol-value name value))
277 ;; Define the constant in the cross-compilation host, since the
278 ;; value is used when cross-compiling for :COMPILE-TOPLEVEL contexts
279 ;; which reference the constant.
280 #+sb-xc-host
281 (eval `(unless (boundp ',name) (defconstant ,name ',value)))
282 (setf (info :variable :kind name) :constant)
283 ;; Deoptimize after changing it to :CONSTANT, and not before, though tbh
284 ;; if your code cares about the timing of PROGV relative to DEFCONSTANT,
285 ;; well, I can't even.
286 #-sb-xc-host (unset-symbol-progv-optimize name)
287 name)
289 (sb-xc:defmacro defvar (var &optional (val nil valp) (doc nil docp))
290 "Define a special variable at top level. Declare the variable
291 SPECIAL and, optionally, initialize it. If the variable already has a
292 value, the old value is not clobbered. The third argument is an optional
293 documentation string for the variable."
294 (check-designator var 'defvar)
295 ;; Maybe kill docstring, but only under the cross-compiler.
296 #+(and (not sb-doc) sb-xc-host) (setq doc nil)
297 `(progn
298 (eval-when (:compile-toplevel)
299 (%compiler-defvar ',var))
300 (%defvar ',var
301 (sb-c:source-location)
302 ,@(cond ((not valp)
303 nil)
304 ((constantp val)
305 ;; No need to avoid evaluation if it's a constant.
306 `(',(constant-form-value val)))
307 (val
308 `((unless (%boundp ',var) ,val))))
309 ,@(and docp
310 `(',doc)))))
312 (sb-xc:defmacro defparameter (var val &optional (doc nil docp))
313 "Define a parameter that is not normally changed by the program,
314 but that may be changed without causing an error. Declare the
315 variable special and sets its value to VAL, overwriting any
316 previous value. The third argument is an optional documentation
317 string for the parameter."
318 (check-designator var 'defparameter)
319 ;; Maybe kill docstring, but only under the cross-compiler.
320 #+(and (not sb-doc) sb-xc-host) (setq doc nil)
321 `(progn
322 (eval-when (:compile-toplevel)
323 (%compiler-defvar ',var))
324 (%defparameter ',var ,val (sb-c:source-location)
325 ,@(and docp
326 `(',doc)))))
328 (defun %compiler-defvar (var)
329 (proclaim `(special ,var)))
332 ;;;; DEFGLOBAL and DEFINE-LOAD-TIME-GLOBAL
334 (sb-xc:defmacro defglobal (name value &optional (doc nil docp))
335 "Defines NAME as a global variable that is always bound. VALUE is evaluated
336 and assigned to NAME both at compile- and load-time, but only if NAME is not
337 already bound.
339 Global variables share their values between all threads, and cannot be
340 locally bound, declared special, defined as constants, and neither bound
341 nor defined as symbol macros.
343 See also the declarations SB-EXT:GLOBAL and SB-EXT:ALWAYS-BOUND."
344 (check-designator name 'defglobal)
345 (let ((boundp (make-symbol "BOUNDP")))
346 `(progn
347 (eval-when (:compile-toplevel)
348 (let ((,boundp (boundp ',name)))
349 (%compiler-defglobal ',name :always-bound
350 (not ,boundp) (unless ,boundp ,value))))
351 (%defglobal ',name
352 (if (%boundp ',name) (make-unbound-marker) ,value)
353 (sb-c:source-location)
354 ,@(and docp `(',doc))))))
356 (sb-xc:defmacro define-load-time-global (name value &optional (doc nil docp))
357 "Defines NAME as a global variable that is always bound. VALUE is evaluated
358 and assigned to NAME at load-time, but only if NAME is not already bound.
360 Attempts to read NAME at compile-time will signal an UNBOUND-VARIABLE error
361 unless it has otherwise been assigned a value.
363 See also DEFGLOBAL which assigns the VALUE at compile-time too."
364 (check-designator name 'define-load-time-global)
365 `(progn
366 (eval-when (:compile-toplevel)
367 (%compiler-defglobal ',name :eventually nil nil))
368 (%defglobal ',name
369 (if (%boundp ',name) (make-unbound-marker) ,value)
370 (sb-c:source-location)
371 ,@(and docp `(',doc)))))
373 (defun %compiler-defglobal (name always-boundp assign-it-p value)
374 (proclaim `(global ,name))
375 (when assign-it-p
376 (set-symbol-global-value name value))
377 (sb-c::process-variable-declaration
378 name 'always-bound
379 ;; don't "weaken" the proclamation if it's in fact always bound now
380 (if (eq (info :variable :always-bound name) :always-bound)
381 :always-bound
382 always-boundp)))
385 ;;;; various conditional constructs
386 (flet ((prognify (forms env)
387 (cond ((not forms) nil)
388 ((and (singleton-p forms)
389 (sb-c:policy env (= sb-c:store-coverage-data 0)))
390 (car forms))
391 (t `(progn ,@forms)))))
392 ;; COND defined in terms of IF
393 (sb-xc:defmacro cond (&rest clauses &environment env)
394 (named-let make-clauses ((clauses clauses))
395 (if (endp clauses)
397 (let ((clause (first clauses))
398 (more (rest clauses)))
399 (with-current-source-form (clauses)
400 (if (atom clause)
401 (error 'simple-type-error
402 :format-control "COND clause is not a ~S: ~S"
403 :format-arguments (list 'cons clause)
404 :expected-type 'cons
405 :datum clause)
406 (let ((test (first clause))
407 (forms (rest clause)))
408 (if (endp forms)
409 `(or ,test ,(make-clauses more))
410 (if (and (eq test t)
411 (not more))
412 ;; THE to preserve non-toplevelness for FOO in
413 ;; (COND (T (FOO)))
414 `(the t ,(prognify forms env))
415 `(if ,test
416 ,(prognify forms env)
417 ,(when more (make-clauses more))))))))))))
419 (sb-xc:defmacro when (test &body forms &environment env)
420 "If the first argument is true, the rest of the forms are
421 evaluated as a PROGN."
422 `(if ,test ,(prognify forms env)))
424 (sb-xc:defmacro unless (test &body forms &environment env)
425 "If the first argument is not true, the rest of the forms are
426 evaluated as a PROGN."
427 `(if ,test nil ,(prognify forms env))))
430 (sb-xc:defmacro return (&optional (value nil))
431 `(return-from nil ,value))
433 ;;;; various sequencing constructs
434 (flet ((prog-expansion-from-let (varlist body-decls let)
435 (multiple-value-bind (body decls) (parse-body body-decls nil)
436 `(block nil
437 (,let ,varlist
438 ,@decls
439 (tagbody ,@body))))))
440 (sb-xc:defmacro prog (varlist &body body-decls)
441 (prog-expansion-from-let varlist body-decls 'let))
442 (sb-xc:defmacro prog* (varlist &body body-decls)
443 (prog-expansion-from-let varlist body-decls 'let*)))
445 (sb-xc:defmacro prog1 (result &body body)
446 (let ((n-result (gensym)))
447 `(let ((,n-result ,result))
448 (progn
449 ,@body
450 ,n-result))))
452 (sb-xc:defmacro prog2 (form1 result &body body)
453 `(prog1 (progn ,form1 ,result) ,@body))
455 ;; AND and OR are defined in terms of IF.
456 (sb-xc:defmacro and (&rest forms)
457 (named-let expand-forms ((nested nil) (forms forms) (ignore-last nil))
458 (cond ((endp forms) t)
459 ((endp (rest forms))
460 (let ((car (car forms)))
461 (cond (nested
462 car)
464 ;; Preserve non-toplevelness of the form!
465 `(the t ,car)))))
466 ((and ignore-last
467 (endp (cddr forms)))
468 (car forms))
469 ;; Better code that way, since the result will only have two
470 ;; values, NIL or the last form, and the precedeing tests
471 ;; will only be used for jumps
472 ((and (not nested) (cddr forms))
473 `(if ,(expand-forms t forms t)
474 ,@(last forms)))
476 `(if ,(first forms)
477 ,(expand-forms t (rest forms) ignore-last))))))
479 (sb-xc:defmacro or (&rest forms)
480 (named-let expand-forms ((nested nil) (forms forms))
481 (cond ((endp forms) nil)
482 ((endp (rest forms))
483 ;; Preserve non-toplevelness of the form!
484 (let ((car (car forms))) (if nested car `(the t ,car))))
486 (let ((n-result (gensym)))
487 `(let ((,n-result ,(first forms)))
488 (if ,n-result
489 ,n-result
490 ,(expand-forms t (rest forms)))))))))
493 ;;;; Multiple value macros:
495 ;;; All the multiple-value receiving forms are defined in terms of
496 ;;; MULTIPLE-VALUE-CALL.
497 (flet ((validate-vars (vars)
498 (with-current-source-form (vars)
499 (unless (and (listp vars) (every #'symbolp vars))
500 (error "Vars is not a list of symbols: ~S" vars)))))
502 (sb-xc:defmacro multiple-value-bind (vars value-form &body body)
503 (validate-vars vars)
504 (if (= (length vars) 1)
505 ;; Not only does it look nicer to reduce to LET in this special case,
506 ;; if might produce better code or at least compile quicker.
507 ;; Certainly for the evaluator it's preferable.
508 `(let ((,(car vars) ,value-form))
509 ,@body)
510 (flet ((maybe-list (x) (if (member x lambda-list-keywords) (list x) x)))
511 (let ((ignore '#:ignore))
512 `(multiple-value-call #'(lambda (&optional ,@(mapcar #'maybe-list vars)
513 &rest ,ignore)
514 (declare (ignore ,ignore))
515 ,@body)
516 ,value-form)))))
518 (sb-xc:defmacro multiple-value-setq (vars value-form)
519 (validate-vars vars)
520 ;; MULTIPLE-VALUE-SETQ is required to always return just the primary
521 ;; value of the value-from, even if there are no vars. (SETF VALUES)
522 ;; in turn is required to return as many values as there are
523 ;; value-places, hence this:
524 (if vars
525 `(values (setf (values ,@vars) ,value-form))
526 `(values ,value-form))))
528 (sb-xc:defmacro multiple-value-list (value-form)
529 `(multiple-value-call #'list ,value-form))
531 (sb-xc:defmacro nth-value (n form &environment env)
532 "Evaluate FORM and return the Nth value (zero based)
533 without consing a temporary list of values."
534 ;; FIXME: The above is true, if slightly misleading. The
535 ;; MULTIPLE-VALUE-BIND idiom [ as opposed to MULTIPLE-VALUE-CALL
536 ;; (LAMBDA (&REST VALUES) (NTH N VALUES)) ] does indeed not cons at
537 ;; runtime. However, for large N (say N = 200), COMPILE on such a
538 ;; form will take longer than can be described as adequate, as the
539 ;; optional dispatch mechanism for the M-V-B gets increasingly
540 ;; hairy.
541 (let ((val (and (constantp n env) (constant-form-value n env))))
542 (if (and (integerp val) (<= 0 val (or #+(or x86-64 arm64 riscv) ;; better DEFAULT-UNKNOWN-VALUES
543 1000
544 10))) ; Arbitrary limit.
545 (let ((dummy-list (make-gensym-list val))
546 (keeper (gensym "KEEPER")))
547 `(multiple-value-bind (,@dummy-list ,keeper) ,form
548 (declare (ignore ,@dummy-list))
549 ,keeper))
550 ;; &MORE conversion handily deals with non-constant N,
551 ;; avoiding the unstylish practice of inserting FORM into the
552 ;; expansion more than once to pick off a few small values.
553 ;; This is not as good as above, because it uses TAIL-CALL-VARIABLE.
554 `(multiple-value-call
555 (lambda (n &rest list) (nth (truly-the index n) list))
556 (the index ,n) ,form))))
559 ;;;; ASSERT and CHECK-TYPE
561 ;;; ASSERT is written this way, to call ASSERT-ERROR, because of how
562 ;;; closures are compiled. RESTART-CASE has forms with closures that
563 ;;; the compiler causes to be generated at the top of any function
564 ;;; using RESTART-CASE, regardless of whether they are needed. Thus if
565 ;;; we just wrapped a RESTART-CASE around the call to ERROR, we'd have
566 ;;; to do a significant amount of work at runtime allocating and
567 ;;; deallocating the closures regardless of whether they were ever
568 ;;; needed.
569 (sb-xc:defmacro assert (test-form &optional places datum &rest arguments
570 &environment env)
571 "Signals an error if the value of TEST-FORM is NIL. Returns NIL.
573 Optional DATUM and ARGUMENTS can be used to change the signaled
574 error condition and are interpreted as in (APPLY #'ERROR DATUM
575 ARGUMENTS).
577 Continuing from the signaled error using the CONTINUE restart will
578 allow the user to alter the values of the SETFable locations
579 specified in PLACES and then start over with TEST-FORM.
581 If TEST-FORM is of the form
583 (FUNCTION ARG*)
585 where FUNCTION is a function (but not a special operator like
586 CL:OR, CL:AND, etc.) the results of evaluating the ARGs will be
587 included in the error report if the assertion fails."
588 (collect ((bindings) (infos))
589 (let* ((func (if (listp test-form) (car test-form)))
590 (new-test
591 (if (and (typep func '(and symbol (not null)))
592 (not (macro-function func env))
593 (not (special-operator-p func))
594 (proper-list-p (cdr test-form)))
595 ;; TEST-FORM is a function call. We do not attempt this
596 ;; if TEST-FORM is a macro invocation or special form.
597 `(,func ,@(mapcar (lambda (place)
598 (if (constantp place env)
599 place
600 (with-unique-names (temp)
601 (bindings `(,temp ,place))
602 (infos `',place)
603 (infos temp)
604 temp)))
605 (rest test-form)))
606 ;; For all other cases, just evaluate TEST-FORM
607 ;; and don't report any details if the assertion fails.
608 test-form))
609 (try '#:try)
610 (done '#:done))
611 ;; If TEST-FORM, potentially using values from BINDINGS, does not
612 ;; hold, enter a loop which reports the assertion error,
613 ;; potentially changes PLACES, and retries TEST-FORM.
614 `(tagbody
615 ,try
616 (let ,(bindings)
617 (when ,new-test
618 (go ,done))
620 (assert-error ',test-form
621 ,@(and (infos)
622 `(,(/ (length (infos)) 2)))
623 ,@(infos)
624 ,@(and (or places datum
625 arguments)
626 `(',places))
627 ,@(and (or places datum
628 arguments)
629 `(,datum))
630 ,@arguments))
631 ,@(mapcar (lambda (place)
632 `(setf ,place (assert-prompt ',place ,place)))
633 places)
634 (go ,try)
635 ,done))))
637 (defun assert-prompt (name value)
638 (cond ((y-or-n-p "The old value of ~S is ~S.~
639 ~%Do you want to supply a new value? "
640 name value)
641 (format *query-io* "~&Type a form to be evaluated:~%")
642 (eval (read *query-io*)))
643 (t value)))
645 ;;; CHECK-TYPE is written this way, to call CHECK-TYPE-ERROR, because
646 ;;; of how closures are compiled. RESTART-CASE has forms with closures
647 ;;; that the compiler causes to be generated at the top of any
648 ;;; function using RESTART-CASE, regardless of whether they are
649 ;;; needed. Because it would be nice if CHECK-TYPE were cheap to use,
650 ;;; and some things (e.g., READ-CHAR) can't afford this excessive
651 ;;; consing, we bend backwards a little.
652 (sb-xc:defmacro check-type (place type &optional type-string
653 &environment env)
654 "Signal a restartable error of type TYPE-ERROR if the value of PLACE
655 is not of the specified type. If an error is signalled and the restart
656 is used to return, this can only return if the STORE-VALUE restart is
657 invoked. In that case it will store into PLACE and start over."
658 ;; Detect a common user-error.
659 (when (and (consp type) (eq 'quote (car type)))
660 (error 'simple-reference-error
661 :format-control "Quoted type specifier in ~S: ~S"
662 :format-arguments (list 'check-type type)
663 :references '((:ansi-cl :macro check-type))))
664 ;; KLUDGE: We use a simpler form of expansion if PLACE is just a
665 ;; variable to work around Python's blind spot in type derivation.
666 ;; For more complex places getting the type derived should not
667 ;; matter so much anyhow.
668 (let ((expanded (%macroexpand place env))
669 (type (let ((ctype (sb-c::careful-specifier-type type)))
670 (if ctype
671 (type-specifier ctype)
672 type))))
673 (if (symbolp expanded)
674 `(do ()
675 ((typep ,place ',type))
676 (setf ,place (check-type-error ',place ,place ',type
677 ,@(and type-string
678 `(,type-string)))))
679 (let ((value (gensym)))
680 `(do ((,value ,place ,place))
681 ((typep ,value ',type))
682 (setf ,place
683 (check-type-error ',place ,value ',type
684 ,@(and type-string
685 `(,type-string)))))))))
687 ;;;; DEFINE-SYMBOL-MACRO
689 (sb-xc:defmacro define-symbol-macro (name expansion)
690 `(eval-when (:compile-toplevel :load-toplevel :execute)
691 (sb-c::%define-symbol-macro ',name ',expansion (sb-c:source-location))))
693 (defun sb-c::%define-symbol-macro (name expansion source-location)
694 (unless (symbolp name)
695 (error 'simple-type-error :datum name :expected-type 'symbol
696 :format-control "Symbol macro name is not a symbol: ~S."
697 :format-arguments (list name)))
698 (with-single-package-locked-error
699 (:symbol name "defining ~A as a symbol-macro"))
700 (let ((kind (info :variable :kind name)))
701 (case kind
702 ((:macro :unknown)
703 (when source-location
704 (setf (info :source-location :symbol-macro name) source-location))
705 (setf (info :variable :kind name) :macro)
706 (setf (info :variable :macro-expansion name) expansion))
708 (%program-error "Symbol ~S is already defined as ~A."
709 name (case kind
710 (:alien "an alien variable")
711 (:constant "a constant")
712 (:special "a special variable")
713 (:global "a global variable")
714 (t kind))))))
715 name)
717 ;;;; DEFINE-COMPILER-MACRO
719 (sb-xc:defmacro define-compiler-macro (name lambda-list &body body)
720 "Define a compiler-macro for NAME."
721 (check-designator name 'define-compiler-macro
722 #'legal-fun-name-p "function name")
723 (when (and (symbolp name) (special-operator-p name))
724 (%program-error "cannot define a compiler-macro for a special operator: ~S"
725 name))
726 ;; DEBUG-NAME is called primarily for its side-effect of asserting
727 ;; that (COMPILER-MACRO-FUNCTION x) is not a legal function name.
728 (let ((def (make-macro-lambda (sb-c::debug-name 'compiler-macro name)
729 lambda-list body 'define-compiler-macro name
730 :accessor 'sb-c::compiler-macro-args)))
731 ;; FIXME: Shouldn't compiler macros also get source locations?
732 ;; Plain DEFMACRO supplies source location information.
733 `(progn
734 (eval-when (:compile-toplevel)
735 (sb-c::%compiler-defmacro :compiler-macro-function ',name))
736 (eval-when (:compile-toplevel :load-toplevel :execute)
737 (sb-c::%define-compiler-macro ',name ,def)))))
739 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
740 (defun sb-c::%define-compiler-macro (name definition)
741 (sb-c::warn-if-compiler-macro-dependency-problem name)
742 ;; FIXME: warn about incompatible lambda list with
743 ;; respect to parent function?
744 (setf (compiler-macro-function name) definition)
745 name))
747 ;;;; CASE, TYPECASE, and friends
749 ;;; Make this a full warning during SBCL build.
750 #+sb-xc ; Don't redefine if recompiling in a warm REPL
751 (define-condition duplicate-case-key-warning (#-sb-xc-host style-warning #+sb-xc-host warning)
752 ((key :initarg :key
753 :reader case-warning-key)
754 (case-kind :initarg :case-kind
755 :reader case-warning-case-kind)
756 (occurrences :initarg :occurrences
757 :type list
758 :reader duplicate-case-key-warning-occurrences))
759 (:report
760 (lambda (condition stream)
761 (format stream
762 "Duplicate key ~S in ~S form, ~
763 occurring in~{~#[~; and~]~{ the ~:R clause:~%~< ~S~:>~}~^,~}."
764 (case-warning-key condition)
765 (case-warning-case-kind condition)
766 (duplicate-case-key-warning-occurrences condition)))))
768 ;;; Return three values:
769 ;;; 1. an array of LAYOUT
770 ;;; 2. an array of (unsigned-byte 16) for the clause index to select
771 ;;; 3. an expression mapping each layout in LAYOUT-LISTS to an integer 0..N-1
772 (defun build-sealed-struct-typecase-map (layout-lists hashes)
773 ;; The hash-generator emulator wants a cookie identifying the set of objects
774 ;; that were hashed.
775 (let ((lambda (sb-c:make-perfect-hash-lambda
776 hashes
777 #+sb-xc-host
778 (map 'vector
779 (lambda (list)
780 (mapcar (lambda (layout)
781 (list :type (classoid-name (layout-classoid layout))))
782 list))
783 layout-lists))))
784 (unless lambda
785 (return-from build-sealed-struct-typecase-map (values nil nil nil)))
786 (let* ((phashfun (sb-c::compile-perfect-hash lambda hashes))
787 (n (length hashes))
788 (domain (make-array n :initial-element nil))
789 (range (sb-xc:make-array n :element-type '(unsigned-byte 16))))
790 (loop for clause-index from 1 for list across layout-lists
791 do (dolist (layout list)
792 (let* ((hash (ldb (byte 32 0) (layout-clos-hash layout)))
793 (index (funcall phashfun hash)))
794 (aver (null (aref domain index)))
795 (setf (aref domain index) layout
796 (aref range index) clause-index))))
797 (values domain range lambda))))
799 (declaim (ftype function sb-pcl::emit-cache-lookup))
800 (defun optimize-%typecase-index (layout-lists object sealed)
801 ;; If no new subtypes can be defined, then there is a compiled-time-computable
802 ;; mapping from CLOS-hash to jump table index.
803 ;; Try the hash-based expansion if applicable. It's allowed to fail, as it will
804 ;; when 32-bit hashes are nonunique.
805 (when sealed
806 ;; TODO: this could eliminate an array lookup when there is only a single layout
807 ;; per clause. So instead of the perfect hash identifying a clause index via lookup,
808 ;; the hash _is_ the clause index; the clauses in the CASE need to be permuted
809 ;; to match the hashes, which doesn't work in the way TYPECASE currently expands.
810 (let ((seen-layouts)
811 (expanded-lists (make-array (length layout-lists) :initial-element nil))
812 (index 0))
813 (flet ((add-to-clause (layout)
814 (unless (member layout seen-layouts)
815 (push layout seen-layouts)
816 (push layout (aref expanded-lists index)))))
817 (dovector (layouts layout-lists)
818 (dolist (layout layouts)
819 ;; unless this layout was in a prior clause
820 (when (add-to-clause layout)
821 (sb-kernel::do-subclassoids ((classoid layout) (layout-classoid layout))
822 (declare (ignore classoid))
823 (add-to-clause layout))))
824 (incf index)))
825 (let ((hashes (map '(array (unsigned-byte 32) (*))
826 (lambda (x) #+64-bit (ldb (byte 32 0) (layout-clos-hash x))
827 #-64-bit (layout-clos-hash x))
828 seen-layouts)))
829 (multiple-value-bind (layouts indices expr)
830 (build-sealed-struct-typecase-map expanded-lists hashes)
831 (when expr
832 (return-from optimize-%typecase-index
833 `(truly-the
834 (integer 0 ,(length layout-lists))
835 (if (not (%instancep ,object))
837 (let* ((l (%instance-layout ,object)) ; layout
838 (h (,expr (ldb (byte 32 0) (layout-clos-hash l))))) ; perfect hash
839 (if (and (< h ,(length layouts)) (eq l (svref ,layouts h)))
840 (aref ,indices h)
841 0))))))))))
842 ;; The generated s-expression is too sensitive to the order LOAD-TIME-VALUE fixups are
843 ;; patched in by cold-init. You'll have a bad time if CACHE-CELL is an unbound-marker.
844 #+sb-xc-host (error "PCL cache won't work for cross-compiled TYPECASE")
845 ;; Use a PCL cache when the sealed logic was inapplicable (or failed due to hash collisions).
846 ;; A cache is usually an improvement over sequential tests but it's impossible to know
847 ;; (the first clause could get taken 99% of the time)
848 (let ((n (length layout-lists)))
849 `(truly-the
850 (integer 0 ,n)
851 (if (not (%instancep ,object))
853 ;; TODO: if we access the cache by layout ID instead of the object,
854 ;; one word can store the layout ID and the clause index
855 ;; (certainly true for 64-bit, maybe not 32).
856 ;; The benefit would be never having to observe a key lacking a value.
857 ;; Also: we don't really need the test for the object layout's hash is 0
858 ;; because it can't be. On the other hand, we might want to utilize
859 ;; this macro on STANDARD-OBJECT.
860 (prog* ((clause 0)
861 (cache-cell
862 (load-time-value
863 ;; Assume the cache will want at least N lines
864 (cons (sb-pcl::make-cache :key-count 1 :size ,n :value t)
865 ,layout-lists)))
866 (cache (car (truly-the cons cache-cell)))
867 (layout (%instance-layout ,object)))
868 (declare (optimize (safety 0)))
869 ,(sb-pcl::emit-cache-lookup 'cache '(layout) 'miss 'clause)
870 (return clause)
871 MISS
872 (return (sb-pcl::%struct-typecase-miss ,object cache-cell)))))))
874 ;;; Decide whether to bind EXPR to a random gensym or a COPY-SYMBOL, or not at all,
875 ;;; for purposes of CASE/TYPECASE. Lexical vars don't require rebinding because
876 ;;; no SET can occur in dispatching to a clause, and multiple refs are devoid
877 ;;; of side-effects (such as UNBOUND-SYMBOL or undefined-alien trap)
878 (defun choose-tempvar (bind expr env)
879 (let ((bind
880 (cond ((or bind (consp expr)) t)
881 ((not (symbolp expr)) nil)
883 (let ((found (and (sb-c::lexenv-p env)
884 (sb-c:lexenv-find expr vars :lexenv env))))
885 (cond ((or (sb-c::global-var-p found)
886 (listp found) ; special, macro, or not found
887 (eq found :bogus)) ; PCL walker shenanigans
889 ((sb-c::lambda-var-specvar found)
890 (bug "can't happen"))
892 nil)))))))
893 (cond ((not bind) expr)
894 ((and (symbolp expr)
895 ;; Some broken 3rd-party code walker is confused by #:_
896 ;; and this hack of forcing a random gensym seems
897 ;; to partially cure whatever the problem is.
898 (string/= expr "_"))
899 (copy-symbol expr))
901 (gensym)))))
903 ;;; Given an arbitrary TYPECASE, see if it is a discriminator over
904 ;;; an assortment of structure-object subtypes. If it is, potentially turn it
905 ;;; into a dispatch based on layout-clos-hash.
906 ;;; The decision to use a hash-based lookup should depend on the number of types
907 ;;; matched, but if there are a lot of types matched all rooted at a common
908 ;;; ancestor, it may not be as beneficial.
910 ;;; The expansion currently works only with sealed classoids.
911 ;;; Making it work with unsealed classoids isn't too tough.
912 ;;; The dispatch will look something like a PCL cache but simpler.
913 ;;; First of all, there's no reason we can't use stable hashes
914 ;;; for structure layouts, because an incompatibly redefined structure
915 ;;; (which is unportable to begin with), doesn't require a new hash.
916 ;;; In fact as far as I can tell, redefining a standard class doesn't require a new hash
917 ;;; because the obsolete layout always gets clobbered to 0, and cache lookups always check
918 ;;; for a match on both the hash and the layout.
919 (defun expand-struct-typecase (keyform normal-clauses type-specs default errorp)
920 (let* ((n (length type-specs))
921 (n-base-types 0)
922 (layout-lists (make-array n))
923 (exhaustive-list) ; of classoids
924 (temp (choose-tempvar t keyform nil))
925 (all-sealed t))
926 (labels
927 ((ok-classoid (classoid)
928 ;; Return T if this is a classoid this expander can work with.
929 ;; Also figure if all classoids accepted by this test were sealed.
930 (when (or (structure-classoid-p classoid)
931 (and (sb-kernel::built-in-classoid-p classoid)
932 (not (memq (classoid-name classoid)
933 sb-kernel::**non-instance-classoid-types**))))
934 ;; If this classoid is sealed, then its children are sealed too,
935 ;; and we don't need to verify that.
936 (unless (eq (classoid-state classoid) :sealed)
937 (setq all-sealed nil))
938 (sb-kernel::do-subclassoids ((subclassoid layout) classoid)
939 (declare (ignore layout))
940 (pushnew subclassoid exhaustive-list))
942 (get-layouts (ctype)
943 (let ((list
944 (cond ((ok-classoid ctype) (list (classoid-layout ctype)))
945 ((and (union-type-p ctype)
946 (every #'ok-classoid (union-type-types ctype)))
947 (mapcar 'classoid-layout (union-type-types ctype))))))
948 (incf n-base-types (length list))
949 list)))
950 ;; For each clause, if it effectively an OR over acceptable instance types,
951 ;; collect the layouts of those types.
952 (loop for i from 0 for spec in type-specs
953 do (let ((parse (specifier-type spec)))
954 (setf (aref layout-lists i) (or (get-layouts parse)
955 (return-from expand-struct-typecase nil)))))
956 ;; The number of base types is an upper bound on the number of different TYPEP
957 ;; executions that could occur.
958 ;; Let's say 1 to 4 TYPEP tests isn't to bad. Just do them sequentially.
959 ;; But given something like:
960 ;; (typecase x
961 ;; ((or parent1 parent2 parent3) ...)
962 ;; ((or parent4 parent5 parent6) ...)
963 ;; where eaach parent has dozens of children (directly or indirectly),
964 ;; it may be worse to use a hash-based lookup.
965 (when (or (< n-base-types 5) ; too few cases
966 (> (length exhaustive-list) (* 3 n-base-types))) ; too much "bloat"
967 (return-from expand-struct-typecase))
968 ;; I don't know if these criteria are sane: Use hashing only if either all sealed,
969 ;; or very large? Why is this an additional restriction beyond the above heuristics?
970 (when (or all-sealed (>= n-base-types 8))
971 `(let ((,temp ,keyform))
972 (case (sb-kernel::%typecase-index ,layout-lists ,temp ,all-sealed)
973 ,@(loop for i from 1 for clause in normal-clauses
974 collect `(,i
975 ;; CLAUSE is ((TYPEP #:G 'a-type) . forms)
976 (sb-c::%type-constraint ,temp ,(third (car clause)))
977 ,@(cdr clause)))
978 (0 ,@(if errorp
979 `((etypecase-failure ,temp ',type-specs))
980 (cdr default)))))))))
982 (defun should-attempt-hash-based-case-dispatch (keys)
983 ;; Guess a good minimum table size, with a slight bias against using the xperfecthash files.
984 ;; If there are a mixture of key types, penalize slightly be requiring a larger minimum
985 ;; number of keys. If we don't do that, then the expression can have a ridiculous amount
986 ;; of math in it that would surely outweigh any savings over an IF/ELSE chain.
987 ;; Technically I should generate the perfect hash function and then decide how costly it is
988 ;; using PHASH-CONVERT-TO-2-OPERAND-CODE as the cost model (number of instructions).
989 (let ((minimum #+sb-xc-host 5 #-sb-xc-host 4))
990 (when (and (some #'symbolp keys) (or (some #'integerp keys) (some #'characterp keys)))
991 (incf minimum 2))
992 (>= (length keys) minimum)))
994 (defun wrap-if (condition with form)
995 (if condition
996 (append with (list form))
997 form))
999 ;;; CASE-BODY returns code for all the standard "case" macros. NAME is
1000 ;;; the macro name, and KEYFORM is the thing to case on.
1001 ;;; When ERRORP, no OTHERWISE-CLAUSEs are recognized,
1002 ;;; and an ERROR or CERROR form is generated where control falls off the end
1003 ;;; of the ordinary clauses.
1005 ;;; Note the absence of EVAL-WHEN here. The cross-compiler calls this function
1006 ;;; and gets the compiled code that the host produced in make-host-1.
1007 ;;; If recompiled, you do not want an interpreted definition that might come
1008 ;;; from EVALing a toplevel form - the stack blows due to infinite recursion.
1009 (defun case-body (whole lexenv test errorp
1010 &aux (clauses ())
1011 (case-clauses (if (eq test 'typep) '(0))) ; generalized boolean
1012 (keys))
1013 (destructuring-bind (name keyform &rest specified-clauses
1014 &aux (keyform-value (choose-tempvar (eq errorp 'cerror)
1015 keyform lexenv)))
1016 whole
1017 (unless (or (cdr whole) (not errorp))
1018 (warn "no clauses in ~S" name))
1019 (do* ((cases specified-clauses (cdr cases))
1020 (clause (car cases) (car cases))
1021 (keys-seen (make-hash-table :test #'eql))
1022 (case-position 1 (1+ case-position)))
1023 ((null cases) nil)
1024 (flet ((check-clause (case-keys)
1025 (loop for k in case-keys
1026 for existing = (gethash k keys-seen)
1027 do (when existing
1028 (warn 'duplicate-case-key-warning
1029 :key k
1030 :case-kind name
1031 :occurrences `(,existing (,case-position (,clause))))))
1032 (let ((record (list case-position (list clause))))
1033 (dolist (k case-keys)
1034 (setf (gethash k keys-seen) record))))
1035 (testify (k)
1036 `(,test ,keyform-value
1037 ,(if (and (eq test 'eql) (self-evaluating-p k)) k `',k))))
1038 (unless (list-of-length-at-least-p clause 1)
1039 (with-current-source-form (cases)
1040 (error "~S -- bad clause in ~S" clause name)))
1041 (with-current-source-form (clause)
1042 ;; https://sourceforge.net/p/sbcl/mailman/message/11863996/ contains discussion
1043 ;; of whether to warn when seeing OTHERWISE in a normal-clause position, but
1044 ;; it is in fact an error: "In the case of case, the symbols t and otherwise
1045 ;; MAY NOT be used as the keys designator."
1046 ;; T in CASE heads an otherwise-clause, but in TYPECASE it's either a plain
1047 ;; type specifier OR it is the otherwise-clause. They're equivalent, but
1048 ;; EXPAND-STRUCT-TYPECASE has a fixed expectation re. normal and otherwise clause
1049 (destructuring-bind (keyoid &rest forms) clause
1050 (when (null forms)
1051 (setq forms '(nil)))
1052 (cond (;; an OTHERWISE-CLAUSE
1053 (and (not errorp) ; possible only in CASE or TYPECASE,
1054 ; not in [EC]CASE or [EC]TYPECASE
1055 (or (eq keyoid 'otherwise)
1056 (and (eq keyoid 't) (or (eq test 'eql) (not (cdr cases))))))
1057 (cond ((null (cdr cases))
1058 (push `(t ,@forms) clauses))
1059 ((eq name 'case)
1060 (error 'simple-reference-error
1061 :format-control
1062 "~@<~IBad ~S clause:~:@_ ~S~:@_~S allowed as the key ~
1063 designator only in the final otherwise-clause, not in a ~
1064 normal-clause. Use (~S) instead, or move the clause to the ~
1065 correct position.~:@>"
1066 :format-arguments (list 'case clause keyoid keyoid)
1067 :references `((:ansi-cl :macro case))))
1069 ;; OTHERWISE is a redundant bit of the behavior of TYPECASE
1070 ;; since T is the universal type. OTHERWISE could not legally
1071 ;; be DEFTYPEed so this _must_ be a misplaced clause.
1072 (error 'simple-reference-error
1073 :format-control
1074 "~@<~IBad ~S clause:~:@_ ~S~:@_~S is allowed only in the final clause. ~
1075 Use T instead, or move the clause to the correct position.~:@>"
1076 :format-arguments (list 'typecase clause keyoid)
1077 :references `((:ansi-cl :macro typecase))))))
1078 ((and (listp keyoid) (eq test 'eql))
1079 (unless (proper-list-p keyoid) ; REVERSE would err with unclear message
1080 (error "~S is not a proper list" keyoid))
1081 (check-clause keyoid)
1082 (setf keys (nconc (reverse keyoid) keys))
1083 ;; This inserts an unreachable clause if KEYOID is NIL, but
1084 ;; FORMS could contain a side-effectful LOAD-TIME-VALUE.
1085 (push `(,(cond ((cdr keyoid) `(or ,@(mapcar #'testify keyoid)))
1086 (keyoid (testify (car keyoid))))
1087 ,@forms)
1088 clauses))
1090 (when (and (eq test 'typep) (eq keyoid t))
1091 ;; - if ERRORP is nil and there are more clauses, this shadows them,
1092 ;; which seems suspicious and worth style-warning for.
1093 ;; - if ERRORP is non-nil, though this isn't technically an "otherwise"
1094 ;; clause, in acts just like one.
1095 (if errorp
1096 (setq errorp :none)))
1097 (when case-clauses ; try the TYPECASE into CASE reduction
1098 (let ((typespec (ignore-errors (typexpand keyoid))))
1099 (cond ((typep typespec '(cons (eql member) (satisfies proper-list-p)))
1100 (push (cons (cdr typespec) forms) case-clauses))
1101 ((and (eq typespec t) (not (cdr cases))) ; one more KLUDGE
1102 (push clause case-clauses))
1104 (setq case-clauses nil)))))
1105 (push keyoid keys)
1106 (check-clause (list keyoid))
1107 (push `(,(testify keyoid) ,@forms) clauses)))))))
1108 (when (eq errorp :none)
1109 (setq errorp nil))
1111 ;; [EC]CASE has an advantage over [EC]TYPECASE in that we readily notice when
1112 ;; the expansion can use symbol-hash to pick the clause.
1113 (when case-clauses
1114 (return-from case-body
1115 `(,(cond ((not errorp) 'case) ((eq name 'ctypecase) 'ccase) (t 'ecase))
1116 ,keyform
1117 ,@(cdr (reverse case-clauses)) ; 1st elt was a boolean flag
1118 ,@(when (eq (caar clauses) t) (list (car clauses))))))
1120 (setq keys
1121 (nreverse (mapcon (lambda (tail)
1122 (unless (member (car tail) (cdr tail))
1123 (list (car tail))))
1124 keys)))
1125 (when (eq test 'typep)
1126 (let (types)
1127 (loop for key in keys
1128 for clause in specified-clauses
1130 (with-current-source-form (clause)
1131 (let ((type (specifier-type key)))
1132 (when (and type
1133 (neq type *empty-type*))
1134 (let ((existing (loop for (prev . spec) in types
1135 when (and (csubtypep type prev)
1136 (not (or (and (eq prev (specifier-type 'single-float))
1137 (eq key 'short-float))
1138 #-long-float
1139 (and (eq prev (specifier-type 'double-float))
1140 (eq key 'long-float))
1141 (and (csubtypep type (specifier-type 'array))
1142 ;; Ignore due to upgrading
1143 (sb-kernel::ctype-array-any-specialization-p prev)))))
1144 return spec)))
1145 (if existing
1146 (style-warn "Clause ~s is shadowed by ~s"
1147 key existing)
1148 (push (cons type key) types)))))))))
1149 ;; Try hash-based dispatch only if expanding for the compiler
1150 (when (and (neq errorp 'cerror)
1151 (sb-c::compiling-p lexenv)
1152 ;; See slow-findhash-allowed
1153 (sb-c:policy lexenv (and (>= speed compilation-speed)
1154 (> sb-c:jump-table 0)))
1155 (sb-c::vop-existsp :named sb-c:jump-table))
1156 (let* ((default (if (eq (caar clauses) 't) (car clauses)))
1157 (normal-clauses (reverse (if default (cdr clauses) clauses))))
1158 ;; Try expanding a using perfect hash and either a jump table or k/v vectors
1159 ;; depending on constant-ness of results.
1160 (cond ((eq test 'typep)
1161 (awhen (expand-struct-typecase keyform normal-clauses keys
1162 default errorp)
1163 (return-from case-body it))))))
1165 (setq clauses (nreverse clauses))
1167 (let ((expected-type `(,(if (eq test 'eql) 'member 'or) ,@keys)))
1168 (when (eq errorp 'cerror) ; CCASE or CTYPECASE
1169 (return-from case-body
1170 ;; It is not a requirement to evaluate subforms of KEYFORM once only, but it often
1171 ;; reduces code size to do so, as the update form will take advantage of typechecks
1172 ;; already performed. (Nor is it _required_ to re-evaluate subforms)
1173 (binding* ((switch (make-symbol "SWITCH"))
1174 (retry
1175 ;; TODO: consider using the union type simplifier algorithm here
1176 `(case-body-error ',name ',keyform ,keyform-value ',expected-type ',keys))
1177 ((vars vals stores writer reader) (get-setf-expansion keyform)))
1178 `(let* ,(mapcar #'list vars vals)
1179 (named-let ,switch ((,keyform-value ,reader))
1180 (cond ,@clauses
1181 (t (multiple-value-bind ,stores ,retry (,switch ,writer)))))))))
1183 (when (and (eq keyform-value keyform) (not keys))
1184 (setq keyform-value '#:dummy)) ; force a rebinding to "use" the value
1185 (let ((switch
1186 `(cond
1187 ,@clauses
1188 ,@(when errorp
1189 `((t
1190 ,(wrap-if
1191 (sb-c::compiling-p lexenv)
1192 '(locally (declare (muffle-conditions code-deletion-note)))
1193 (ecase name
1194 (etypecase
1195 `(etypecase-failure
1196 ,keyform-value ,(etypecase-error-spec keys)))
1197 (ecase
1198 `(ecase-failure ,keyform-value ',keys))))))))))
1199 (if (eq keyform-value keyform)
1200 switch
1201 `(let ((,keyform-value ,keyform))
1202 ;; binding must be IGNORABLE in either of these expressions:
1203 ;; (CASE KEY (() 'res))
1204 ;; (CASE KEY (T 'res))
1205 (declare (ignorable ,keyform-value))
1206 ,switch))))))
1208 ;;; ETYPECASE over clauses that form a "simpler" type specifier should use that,
1209 ;;; e.g. partitions of INTEGER:
1210 ;;; (etypecase ((integer * -1) ...) ((eql 0) ...) ((integer 1 *) ...))
1211 ;;; (etypecase (fixnum ...) (bignum ...))
1212 (defun etypecase-error-spec (types)
1213 (when (cdr types) ; no sense in doing this for a single type
1214 (let ((parsed (mapcar #'sb-c::careful-specifier-type types)))
1215 (when (every (lambda (x) (and x (not (contains-unknown-type-p x))))
1216 parsed)
1217 (let* ((union (apply #'type-union parsed))
1218 (unparsed (type-specifier union)))
1219 ;; If the type-union of the types is a simpler expression than (OR ...),
1220 ;; then return the simpler one. CTYPECASE could do this also, but doesn't.
1221 ;; http://www.lispworks.com/documentation/HyperSpec/Body/m_tpcase.htm#etypecase
1222 ;; "If no normal-clause matches, a non-correctable error of type type-error
1223 ;; is signaled. The offending datum is the test-key and the expected type
1224 ;; is /type equivalent/ to (or type1 type2 ...)"
1225 (when (symbolp unparsed)
1226 (return-from etypecase-error-spec `',unparsed))))))
1227 ;; This constant can make its way into generic function dispatch.
1228 ;; The compiled code must not to point to an arena if one is active.
1229 `',(ensure-heap-list types))
1231 (sb-xc:defmacro case (&whole form &environment env &rest r)
1232 (declare (sb-c::lambda-list (keyform &body cases)) (ignore r))
1233 "CASE Keyform {({(Key*) | Key} Form*)}*
1234 Evaluates the Forms in the first clause with a Key EQL to the value of
1235 Keyform. If a singleton key is T then the clause is a default clause."
1236 (case-body form env 'eql nil))
1238 (sb-xc:defmacro ccase (&whole form &environment env &rest r)
1239 (declare (sb-c::lambda-list (keyform &body cases)) (ignore r))
1240 "CCASE Keyform {({(Key*) | Key} Form*)}*
1241 Evaluates the Forms in the first clause with a Key EQL to the value of
1242 Keyform. If none of the keys matches then a correctable error is
1243 signalled."
1244 (case-body form env 'eql 'cerror))
1246 (sb-xc:defmacro ecase (&whole form &environment env &rest r)
1247 (declare (sb-c::lambda-list (keyform &body cases)) (ignore r))
1248 "ECASE Keyform {({(Key*) | Key} Form*)}*
1249 Evaluates the Forms in the first clause with a Key EQL to the value of
1250 Keyform. If none of the keys matches then an error is signalled."
1251 (case-body form env 'eql 'error))
1253 (sb-xc:defmacro typecase (&whole form &environment env &rest r)
1254 (declare (sb-c::lambda-list (keyform &body cases)) (ignore r))
1255 "TYPECASE Keyform {(Type Form*)}*
1256 Evaluates the Forms in the first clause for which TYPEP of Keyform and Type
1257 is true."
1258 (case-body form env 'typep nil))
1260 (sb-xc:defmacro ctypecase (&whole form &environment env &rest r)
1261 (declare (sb-c::lambda-list (keyform &body cases)) (ignore r))
1262 "CTYPECASE Keyform {(Type Form*)}*
1263 Evaluates the Forms in the first clause for which TYPEP of Keyform and Type
1264 is true. If no form is satisfied then a correctable error is signalled."
1265 (case-body form env 'typep 'cerror))
1267 (sb-xc:defmacro etypecase (&whole form &environment env &rest r)
1268 (declare (sb-c::lambda-list (keyform &body cases)) (ignore r))
1269 "ETYPECASE Keyform {(Type Form*)}*
1270 Evaluates the Forms in the first clause for which TYPEP of Keyform and Type
1271 is true. If no form is satisfied then an error is signalled."
1272 (case-body form env 'typep 'error))
1274 ;;; Compile a version of BODY for all TYPES, and dispatch to the
1275 ;;; correct one based on the value of VAR. This was originally used
1276 ;;; only for strings, hence the name. Renaming it to something more
1277 ;;; generic might not be a bad idea.
1278 (sb-xc:defmacro string-dispatch ((&rest types) var &body body)
1279 (let ((fun (gensym "STRING-DISPATCH-FUN")))
1280 `(flet ((,fun (,var)
1281 ,@body))
1282 (declare (inline ,fun))
1283 (etypecase ,var
1284 ,@(loop for type in types
1285 ;; TRULY-THE allows transforms to take advantage of the type
1286 ;; information without need for constraint propagation.
1287 collect `(,type (,fun (truly-the ,type ,var))))))))
1289 ;;;; WITH-FOO i/o-related macros
1291 (sb-xc:defmacro with-open-stream ((var stream) &body body)
1292 (multiple-value-bind (forms decls) (parse-body body nil)
1293 `(let ((,var ,stream))
1294 ,@decls
1295 (unwind-protect
1296 (progn ,@forms)
1297 (close ,var)))))
1299 (sb-xc:defmacro with-open-file ((stream filespec &rest options)
1300 &body body)
1301 (multiple-value-bind (forms decls) (parse-body body nil)
1302 (let ((abortp (gensym)))
1303 `(let ((,stream (open ,filespec ,@options))
1304 (,abortp t))
1305 ,@decls
1306 (unwind-protect
1307 (multiple-value-prog1
1308 (progn ,@forms)
1309 (setq ,abortp nil))
1310 (when ,stream
1311 (close ,stream :abort ,abortp)))))))
1313 ;;;; Iteration macros:
1315 (flet
1316 ((frob-do-body (varlist endlist decls-and-code bind step name block)
1317 ;; Check for illegal old-style DO.
1318 (when (not (listp varlist))
1319 (with-current-source-form (varlist)
1320 (error "~@<Ill-formed ~S variable list -- possibly illegal ~
1321 old style DO?~@:>"
1322 name)))
1323 (when (atom endlist)
1324 (with-current-source-form (endlist)
1325 (error "~@<Ill-formed ~S end test list -- possibly illegal ~
1326 old style DO?~@:>"
1327 name)))
1328 (collect ((steps))
1329 (let ((inits
1330 (with-current-source-form (varlist)
1331 (mapcar (lambda (var)
1332 (with-current-source-form (var)
1333 (or (cond ((symbolp var) (list var))
1334 ((listp var)
1335 (unless (symbolp (first var))
1336 (error "~S step variable is not a symbol: ~S"
1337 name (first var)))
1338 (case (length var)
1339 ((1 2) var)
1340 (3 (steps (first var) (third var))
1341 (list (first var) (second var))))))
1342 (error "~S is an illegal form for a ~S varlist."
1343 var name))))
1344 varlist))))
1345 (multiple-value-bind (code decls) (parse-body decls-and-code nil)
1346 (let ((label-1 (gensym)) (label-2 (gensym)))
1347 `(block ,block
1348 (,bind ,inits
1349 ,@decls
1350 (declare (ignorable ,@(mapcar #'car inits)))
1351 (tagbody
1352 (go ,label-2)
1353 ,label-1
1354 (tagbody ,@code)
1355 (,step ,@(steps))
1356 ,label-2
1357 (unless ,(first endlist) (go ,label-1))
1358 (return-from ,block (progn ,@(rest endlist))))))))))))
1360 ;; This is like DO, except it has no implicit NIL block.
1361 (sb-xc:defmacro do-anonymous (varlist endlist &rest body)
1362 (frob-do-body varlist endlist body 'let 'psetq 'do-anonymous (gensym)))
1364 (sb-xc:defmacro do (varlist endlist &body body)
1365 "DO ({(Var [Init] [Step])}*) (Test Exit-Form*) Declaration* Form*
1366 Iteration construct. Each Var is initialized in parallel to the value of the
1367 specified Init form. On subsequent iterations, the Vars are assigned the
1368 value of the Step form (if any) in parallel. The Test is evaluated before
1369 each evaluation of the body Forms. When the Test is true, the Exit-Forms
1370 are evaluated as a PROGN, with the result being the value of the DO. A block
1371 named NIL is established around the entire expansion, allowing RETURN to be
1372 used as an alternate exit mechanism."
1373 (frob-do-body varlist endlist body 'let 'psetq 'do nil))
1375 (sb-xc:defmacro do* (varlist endlist &body body)
1376 "DO* ({(Var [Init] [Step])}*) (Test Exit-Form*) Declaration* Form*
1377 Iteration construct. Each Var is initialized sequentially (like LET*) to the
1378 value of the specified Init form. On subsequent iterations, the Vars are
1379 sequentially assigned the value of the Step form (if any). The Test is
1380 evaluated before each evaluation of the body Forms. When the Test is true,
1381 the Exit-Forms are evaluated as a PROGN, with the result being the value
1382 of the DO. A block named NIL is established around the entire expansion,
1383 allowing RETURN to be used as an alternate exit mechanism."
1384 (frob-do-body varlist endlist body 'let* 'setq 'do* nil)))
1386 (sb-xc:defmacro dotimes ((var count &optional (result nil)) &body body)
1387 ;; A nice optimization would be that if VAR is never referenced,
1388 ;; it's slightly more efficient to count backwards, but that's tricky.
1389 (let ((c (if (integerp count) count (gensym))))
1390 `(do ((,var 0 (1+ ,var))
1391 ,@(if (symbolp c) `((,c (the integer ,count)))))
1392 ((>= ,var ,c) ,result)
1393 (declare (type unsigned-byte ,var))
1394 ,@body)))
1396 (defun segregate-dolist-decls (var decls)
1397 (collect ((bound-type-decls)
1398 (bound-nontype-decls)
1399 (free-decls))
1400 (dolist (decl decls)
1401 (aver (eq (car decl) 'declare))
1402 (dolist (expr (cdr decl))
1403 (let ((head (car expr))
1404 (tail (cdr expr)))
1405 (cond ((consp head) ; compound type specifier
1406 (when (member var tail) (bound-type-decls head))
1407 (awhen (remove var tail) (free-decls `(,head ,@it))))
1408 ((not (symbolp head)) (free-decls expr)) ; bogus
1410 (case head
1411 ((special dynamic-extent)
1412 ;; dynamic-extent makes no sense but this logic has to correctly
1413 ;; recognize all the standard atoms that DECLARE accepts.
1414 (when (member var tail) (bound-nontype-decls `(,head ,var)))
1415 (awhen (remove var tail) (free-decls `(,head ,@it))))
1416 (type
1417 (when (member var (cdr tail)) (bound-type-decls (cadr expr)))
1418 (awhen (remove var (cdr tail)) (free-decls `(type ,(cadr expr) ,@it))))
1419 ((ignore ignorable)
1420 (awhen (remove var tail) (free-decls `(,head ,@it))))
1421 ((optimize ftype inline notinline maybe-inline
1422 muffle-conditions unmuffle-conditions)
1423 (free-decls expr))
1425 ;; Assume that any decl pertaining to bindings must have the symbol appear
1426 ;; in TAIL. Is this true of custom decls? I would certainly think so.
1427 (cond ((not (member var tail)) (free-decls expr))
1428 ((info :declaration :known head)
1429 ;; Declaimed declaration can't be a type decl.
1430 (bound-nontype-decls expr))
1431 ((not (sb-c::careful-specifier-type head))
1432 ;; If can't be parsed, then what is it? A free decl is as good as anything
1433 (free-decls expr))
1434 ((contains-unknown-type-p (sb-c::careful-specifier-type head))
1435 ;; Stuff it into bound-nontype decls which is no worse
1436 ;; than what FILTER-DOLIST-DECLARATIONS could do.
1437 (bound-nontype-decls expr))
1439 ;; A valid type declaration can pertain to some non-bound vars and/or
1440 ;; the bound var, nicely handling (STRING x y iterationvar).
1441 (when (member var tail) (bound-type-decls head))
1442 (awhen (remove var tail) (free-decls `(,head ,@it))))))))))))
1443 (values (mapcar (lambda (x) `(type ,x ,var)) (bound-type-decls))
1444 (mapcar (lambda (x) `(type (or null ,x) ,var)) (bound-type-decls))
1445 (bound-nontype-decls)
1446 (free-decls))))
1448 (sb-xc:defmacro dolist ((var list &optional (result nil)) &body body &environment env)
1449 ;; We repeatedly bind the var instead of setting it so that we never
1450 ;; have to give the var an arbitrary value such as NIL (which might
1451 ;; conflict with a declaration). If there is a result form, we
1452 ;; introduce a gratuitous binding of the variable to NIL without the
1453 ;; declarations, then evaluate the result form in that
1454 ;; environment. We spuriously reference the gratuitous variable,
1455 ;; since we don't want to use IGNORABLE on what might be a special
1456 ;; var.
1457 (binding* (((forms decls) (parse-body body nil))
1458 ((iter-type-decl res-type-decl other-decl free-decl)
1459 (segregate-dolist-decls var decls))
1460 (n-list (gensym "LIST"))
1461 (start (gensym "START"))
1462 ((clist members clist-ok)
1463 (with-current-source-form (list)
1464 (cond
1465 ((constantp list env)
1466 (binding* ((value (constant-form-value list env))
1467 ((all dot) (list-members value :max-length 20)))
1468 (when (eql dot t)
1469 ;; Full warning is too much: the user may terminate the loop
1470 ;; early enough. Contents are still right, though.
1471 (style-warn "Dotted list ~S in DOLIST." value))
1472 (if (eql dot :maybe)
1473 (values value nil nil)
1474 (values value all t))))
1475 ((and (consp list) (eq 'list (car list))
1476 (every (lambda (arg) (constantp arg env)) (cdr list)))
1477 (let ((values (mapcar (lambda (arg) (constant-form-value arg env)) (cdr list))))
1478 (values values values t)))
1480 (values nil nil nil))))))
1481 `(block nil
1482 (let ((,n-list ,(if clist-ok
1483 (list 'quote clist)
1484 ;; Don't want to use a cast because
1485 ;; the type will actually be checked by ENDP first.
1486 ;; But it doesn't detect the mismatch because the SETF
1487 ;; mixes in T with the initial type.
1488 `(the* (list :use-annotations t :source-form ,list) ,list))))
1489 ,@(when free-decl `((declare ,@free-decl)))
1490 (tagbody
1491 ,start
1492 (unless (endp ,n-list)
1493 (let ((,var ,(if clist-ok
1494 `(truly-the (member ,@members) (car ,n-list))
1495 `(car ,n-list))))
1496 (declare ,@iter-type-decl ,@other-decl (ignorable ,var))
1497 (setq ,n-list (cdr ,n-list))
1498 (tagbody ,@forms))
1499 (go ,start)))
1500 ;; still within the scope of decls pertinent to other than the VAR binding
1501 ,@(when result
1502 `((let ((,var nil))
1503 ,@(if (or res-type-decl other-decl) `((declare ,@res-type-decl ,@other-decl)))
1504 ,var
1505 ,result)))))))
1508 ;;;; Miscellaneous macros:
1510 (sb-xc:defmacro lambda (&whole whole args &body body)
1511 (declare (ignore args body))
1512 `#',whole)
1514 (sb-xc:defmacro named-lambda (&whole whole name args &body body)
1515 (declare (ignore name args body))
1516 `#',whole)
1518 (sb-xc:defmacro declaim (&rest specs)
1519 "DECLAIM Declaration*
1520 Do a declaration or declarations for the global environment."
1521 `(eval-when (:compile-toplevel :load-toplevel :execute)
1522 ,@(mapcar (lambda (spec)
1523 `(sb-c::%proclaim ',spec (sb-c:source-location)))
1524 specs)))
1526 (sb-xc:defmacro print-unreadable-object ((object stream &key type identity)
1527 &body body)
1528 "Output OBJECT to STREAM with \"#<\" prefix, \">\" suffix, optionally
1529 with object-type prefix and object-identity suffix, and executing the
1530 code in BODY to provide possible further output."
1531 ;; Note: possibly out-of-order keyword argument evaluation.
1532 ;; But almost always the :TYPE and :IDENTITY are each literal T or NIL,
1533 ;; and so the LOGIOR expression reduces to a fixed value from 0 to 3.
1534 (let ((call `(%print-unreadable-object
1535 ,object ,stream (logior (if ,type 1 0) (if ,identity 2 0)))))
1536 (if body
1537 (let ((fun (make-symbol "THUNK")))
1538 `(dx-flet ((,fun () (progn ,@body))) (,@call #',fun)))
1539 call)))
1541 ;; A macroexpander helper. Not sure where else to put this.
1542 (defun funarg-bind/call-forms (funarg arg-forms)
1543 (if (typep funarg
1544 '(or (cons (eql function) (cons (satisfies legal-fun-name-p) null))
1545 (cons (eql quote) (cons symbol null))
1546 (cons (eql lambda))))
1547 (values nil `(funcall ,funarg . ,arg-forms))
1548 (let ((fn-sym (gensym))) ; for ONCE-ONLY-ish purposes
1549 (values `((,fn-sym (%coerce-callable-to-fun ,funarg)))
1550 `(sb-c::%funcall ,fn-sym . ,arg-forms)))))
1552 ;;; Ordinarily during self-build, nothing would need this macro except the
1553 ;;; calls in src/code/list, and src/code/seq.
1554 ;;; However, if cons profiling is enbled, then all calls to COPY-LIST
1555 ;;; transform into the macro, so it must be available early.
1556 (sb-xc:defmacro copy-list-macro (input &key check-proper-list)
1557 ;; Unless CHECK-PROPER-LIST is true, the list is copied correctly
1558 ;; even if the list is not terminated by NIL. The new list is built
1559 ;; by CDR'ing SPLICE which is always at the tail of the new list.
1560 (with-unique-names (orig copy splice cell)
1561 ;; source transform gave input the ONCE-ONLY treatment already.
1562 `(when ,input
1563 (let ((,copy (list (car ,input))))
1564 (do ((,orig (cdr ,input) (cdr ,orig))
1565 (,splice ,copy
1566 (let ((,cell (list (car ,orig))))
1567 (rplacd (truly-the cons ,splice) ,cell)
1568 ,cell)))
1569 (,@(if check-proper-list
1570 `((endp ,orig))
1571 `((atom ,orig)
1572 ;; always store the CDR even if NIL. A blind write
1573 ;; is cheaper than a branch around a write.
1574 (rplacd (truly-the cons ,splice) ,orig)))
1575 ,copy))))))
1577 (defun expand-with-output-to-string (var element-type body wild-result-type)
1578 ;; This is simpler than trying to arrange transforms that cause
1579 ;; MAKE-STRING-OUTPUT-STREAM to be DXable. While that might be awesome,
1580 ;; this macro exists for a reason.
1581 (let* ((initial-buffer '#:buf)
1582 (dummy '#:stream)
1583 (string-ctor
1584 (if (and (sb-xc:constantp element-type)
1585 (let ((ctype (sb-c::careful-specifier-type
1586 (constant-form-value element-type))))
1587 (and ctype
1588 (csubtypep ctype (specifier-type 'character))
1589 (neq ctype *empty-type*))))
1590 ;; Using MAKE-ARRAY avoids a style-warning if et is 'STANDARD-CHAR:
1591 ;; "The default initial element #\Nul is not a STANDARD-CHAR."
1592 'make-array ; hooray! it's known be a valid string type
1593 ;; Force a runtime STRINGP check unless futher transforms
1594 ;; deduce a known type.
1595 'make-string)))
1596 ;; A full call to MAKE-STRING-OUTPUT-STREAM uses a larger initial buffer
1597 ;; if BASE-CHAR but I really don't care to think about that here.
1598 `(let ((,initial-buffer (,string-ctor 31 :element-type ,element-type)))
1599 (declare (dynamic-extent ,initial-buffer))
1600 (dx-let ((,dummy (%allocate-string-ostream)))
1601 (let ((,var (%init-string-output-stream ,dummy ,initial-buffer
1602 ,wild-result-type)))
1603 (declare (ignorable ,var))
1604 ,@body)
1605 (get-output-stream-string ,dummy)))))
1608 ;;;; COMPARE-AND-SWAP
1609 ;;;;
1610 ;;;; SB-EXT:COMPARE-AND-SWAP is the public API for now.
1611 ;;;;
1612 ;;;; Internally our interface has CAS, GET-CAS-EXPANSION,
1613 ;;;; DEFCAS, and #'(CAS ...) functions.
1615 (defun expand-structure-slot-cas (info name place)
1616 (let* ((dd (car info))
1617 (structure (dd-name dd))
1618 (slotd (cdr info))
1619 (index (dsd-index slotd))
1620 (type (dsd-type slotd))
1621 (casser
1622 (case (dsd-raw-type slotd)
1623 ((t) '%instance-cas)
1624 #+(or arm64 ppc ppc64 riscv x86 x86-64)
1625 ((word) '%raw-instance-cas/word)
1626 #+(or arm64 riscv x86 x86-64)
1627 ((sb-vm:signed-word) '%raw-instance-cas/signed-word))))
1628 (unless casser
1629 (error "Cannot use COMPARE-AND-SWAP with structure accessor ~
1630 for a typed slot: ~S"
1631 place))
1632 (when (dsd-read-only slotd)
1633 (error "Cannot use COMPARE-AND-SWAP with structure accessor ~
1634 for a read-only slot: ~S"
1635 place))
1636 (destructuring-bind (op arg) place
1637 (aver (eq op name))
1638 (with-unique-names (instance old new)
1639 (values (list instance)
1640 (list `(the ,structure ,arg))
1643 `(truly-the (values ,type &optional)
1644 (,casser ,instance ,index
1645 (the ,type ,old)
1646 (the ,type ,new)))
1647 `(,op ,instance))))))
1649 ;;; FIXME: remove (it's EXPERIMENTAL, so doesn't need to go through deprecation)
1650 (defun get-cas-expansion (place &optional environment)
1651 "Analogous to GET-SETF-EXPANSION. Returns the following six values:
1653 * list of temporary variables
1655 * list of value-forms whose results those variable must be bound
1657 * temporary variable for the old value of PLACE
1659 * temporary variable for the new value of PLACE
1661 * form using the aforementioned temporaries which performs the
1662 compare-and-swap operation on PLACE
1664 * form using the aforementioned temporaries with which to perform a volatile
1665 read of PLACE
1667 Example:
1669 (get-cas-expansion '(car x))
1670 ; => (#:CONS871), (X), #:OLD872, #:NEW873,
1671 ; (SB-KERNEL:%COMPARE-AND-SWAP-CAR #:CONS871 #:OLD872 :NEW873).
1672 ; (CAR #:CONS871)
1674 (defmacro my-atomic-incf (place &optional (delta 1) &environment env)
1675 (multiple-value-bind (vars vals old new cas-form read-form)
1676 (get-cas-expansion place env)
1677 (let ((delta-value (gensym \"DELTA\")))
1678 `(let* (,@(mapcar 'list vars vals)
1679 (,old ,read-form)
1680 (,delta-value ,delta)
1681 (,new (+ ,old ,delta-value)))
1682 (loop until (eq ,old (setf ,old ,cas-form))
1683 do (setf ,new (+ ,old ,delta-value)))
1684 ,new))))
1686 EXPERIMENTAL: Interface subject to change."
1687 ;; FIXME: this seems wrong on two points:
1688 ;; 1. if TRULY-THE had a CAS expander (which it doesn't) we'd want
1689 ;; to use %MACROEXPAND[-1] so as not to lose the "truly-the"-ness
1690 ;; 2. if both a CAS expander and a macro exist, the CAS expander
1691 ;; should be preferred before macroexpanding (just like SETF does)
1692 (let ((expanded (macroexpand place environment)))
1693 (flet ((invalid-place ()
1694 (error "Invalid place to CAS: ~S -> ~S" place expanded)))
1695 (unless (consp expanded)
1696 (cond ((and (symbolp expanded)
1697 (member (info :variable :kind expanded)
1698 '(:global :special)))
1699 (setq expanded `(symbol-value ',expanded)))
1701 (invalid-place))))
1702 (let ((name (car expanded)))
1703 (unless (symbolp name)
1704 (invalid-place))
1705 (acond
1706 ((info :cas :expander name)
1707 ;; CAS expander.
1708 (funcall it expanded environment))
1710 ;; Structure accessor
1711 ((structure-instance-accessor-p name)
1712 (expand-structure-slot-cas it name expanded))
1714 ;; CAS function
1716 (with-unique-names (old new)
1717 (let ((vars nil)
1718 (vals nil)
1719 (args nil))
1720 (dolist (x (reverse (cdr expanded)))
1721 (cond ((constantp x environment)
1722 (push x args))
1724 (let ((tmp (gensymify x)))
1725 (push tmp args)
1726 (push tmp vars)
1727 (push x vals)))))
1728 (values vars vals old new
1729 `(funcall #'(cas ,name) ,old ,new ,@args)
1730 `(,name ,@args))))))))))
1733 ;;; This is what it all comes down to.
1734 ;;; Possible todo: implement CAS-WEAK like in C and C++ standards
1735 ;;; so that we don't loop-in-a-loop where failure has to re-test
1736 ;;; whether some item is in a list, and retry the CAS anyway.
1737 (sb-xc:defmacro cas (place old new &environment env)
1738 "Synonym for COMPARE-AND-SWAP.
1740 Additionally DEFUN, DEFGENERIC, DEFMETHOD, FLET, and LABELS can be also used to
1741 define CAS-functions analogously to SETF-functions:
1743 (defvar *foo* nil)
1745 (defun (cas foo) (old new)
1746 (cas (symbol-value '*foo*) old new))
1748 First argument of a CAS function is the expected old value, and the second
1749 argument of is the new value. Note that the system provides no automatic
1750 atomicity for CAS functions, nor can it verify that they are atomic: it is up
1751 to the implementor of a CAS function to ensure its atomicity.
1753 EXPERIMENTAL: Interface subject to change."
1754 ;; It's not necessary that GET-CAS-EXPANSION work on defined alien vars.
1755 ;; They're not generalized places in the sense that they could hold any object,
1756 ;; so there's very little point to being more general.
1757 ;; In particular, allowing ATOMIC-PUSH or ATOMIC-POP on them is wrong.
1758 (awhen (and (symbolp place)
1759 (eq (info :variable :kind place) :alien)
1760 (sb-alien::cas-alien place old new))
1761 (return-from cas it))
1762 (multiple-value-bind (temps place-args old-temp new-temp cas-form)
1763 (get-cas-expansion place env)
1764 `(let* (,@(mapcar #'list temps place-args)
1765 (,old-temp ,old)
1766 (,new-temp ,new))
1767 ,cas-form)))
1769 (sb-xc:defmacro compare-and-swap (place old new)
1770 "Atomically stores NEW in PLACE if OLD matches the current value of PLACE.
1771 Two values are considered to match if they are EQ. Returns the previous value
1772 of PLACE: if the returned value is EQ to OLD, the swap was carried out.
1774 PLACE must be an CAS-able place. Built-in CAS-able places are accessor forms
1775 whose CAR is one of the following:
1777 CAR, CDR, FIRST, REST, SVREF, SYMBOL-PLIST, SYMBOL-VALUE, SVREF, SLOT-VALUE
1778 SB-MOP:STANDARD-INSTANCE-ACCESS, SB-MOP:FUNCALLABLE-STANDARD-INSTANCE-ACCESS,
1780 or the name of a DEFSTRUCT created accessor for a slot whose storage type
1781 is not raw. (Refer to the the \"Efficiency\" chapter of the manual
1782 for the list of raw slot types. Future extensions to this macro may allow
1783 it to work on some raw slot types.)
1785 In case of SLOT-VALUE, if the slot is unbound, SLOT-UNBOUND is called unless
1786 OLD is EQ to SB-PCL:+SLOT-UNBOUND+ in which case SB-PCL:+SLOT-UNBOUND+ is
1787 returned and NEW is assigned to the slot. Additionally, the results are
1788 unspecified if there is an applicable method on either
1789 SB-MOP:SLOT-VALUE-USING-CLASS, (SETF SB-MOP:SLOT-VALUE-USING-CLASS), or
1790 SB-MOP:SLOT-BOUNDP-USING-CLASS.
1792 Additionally, the PLACE can be a anything for which a CAS-function has
1793 been defined. (See SB-EXT:CAS for more information.)
1795 `(cas ,place ,old ,new))
1798 ;;;; ATOMIC-INCF and ATOMIC-DECF
1800 (defun expand-atomic-frob
1801 (name specified-place diff env
1802 &aux (place (macroexpand specified-place env)))
1803 (declare (type (member atomic-incf atomic-decf) name))
1804 (flet ((invalid-place ()
1805 (error "Invalid first argument to ~S: ~S" name specified-place))
1806 (compute-newval (old) ; used only if no atomic inc vop
1807 `(logand (,(case name (atomic-incf '+) (atomic-decf '-)) ,old
1808 (the sb-vm:signed-word ,diff)) sb-ext:most-positive-word))
1809 (compute-delta () ; used only with atomic inc vop
1810 `(logand ,(case name
1811 (atomic-incf `(the sb-vm:signed-word ,diff))
1812 (atomic-decf `(- (the sb-vm:signed-word ,diff))))
1813 sb-ext:most-positive-word)))
1814 (declare (ignorable #'compute-newval #'compute-delta))
1815 (when (and (symbolp place)
1816 (eq (info :variable :kind place) :global)
1817 (type= (info :variable :type place) (specifier-type 'fixnum)))
1818 ;; Global can't be lexically rebound.
1819 (return-from expand-atomic-frob
1820 `(truly-the fixnum (,(case name
1821 (atomic-incf '%atomic-inc-symbol-global-value)
1822 (atomic-decf '%atomic-dec-symbol-global-value))
1823 ',place (the fixnum ,diff)))))
1824 (unless (consp place) (invalid-place))
1825 (destructuring-bind (op . args) place
1826 ;; FIXME: The lexical environment should not be disregarded.
1827 ;; CL builtins can't be lexically rebound, but structure accessors can.
1828 (case op
1829 (aref
1830 (unless (singleton-p (cdr args))
1831 (invalid-place))
1832 (with-unique-names (array)
1833 `(let ((,array (the (simple-array word (*)) ,(car args))))
1834 #+compare-and-swap-vops
1835 (%array-atomic-incf/word
1836 ,array
1837 (check-bound ,array (array-dimension ,array 0) ,(cadr args))
1838 ,(compute-delta))
1839 #-compare-and-swap-vops
1840 ,(with-unique-names (index old-value)
1841 `(without-interrupts
1842 (let* ((,index ,(cadr args))
1843 (,old-value (aref ,array ,index)))
1844 (setf (aref ,array ,index) ,(compute-newval old-value))
1845 ,old-value))))))
1846 ((car cdr first rest)
1847 (when (cdr args)
1848 (invalid-place))
1849 `(truly-the
1850 fixnum
1851 (,(case op
1852 ((first car) (case name
1853 (atomic-incf '%atomic-inc-car)
1854 (atomic-decf '%atomic-dec-car)))
1855 ((rest cdr) (case name
1856 (atomic-incf '%atomic-inc-cdr)
1857 (atomic-decf '%atomic-dec-cdr))))
1858 ,(car args) (the fixnum ,diff))))
1860 (when (or (cdr args)
1861 ;; Because accessor info is identical for the writer and reader
1862 ;; functions, without a SYMBOLP check this would erroneously allow
1863 ;; (ATOMIC-INCF ((SETF STRUCT-SLOT) x))
1864 (not (symbolp op))
1865 (not (structure-instance-accessor-p op)))
1866 (invalid-place))
1867 (let* ((accessor-info (structure-instance-accessor-p op))
1868 (slotd (cdr accessor-info))
1869 (type (dsd-type slotd)))
1870 (unless (and (eq 'sb-vm:word (dsd-raw-type slotd))
1871 (type= (specifier-type type) (specifier-type 'sb-vm:word)))
1872 (error "~S requires a slot of type (UNSIGNED-BYTE ~S), not ~S: ~S"
1873 name sb-vm:n-word-bits type place))
1874 (when (dsd-read-only slotd)
1875 (error "Cannot use ~S with structure accessor for a read-only slot: ~S"
1876 name place))
1877 #+compare-and-swap-vops
1878 `(truly-the sb-vm:word
1879 (%raw-instance-atomic-incf/word
1880 (the ,(dd-name (car accessor-info)) ,@args)
1881 ,(dsd-index slotd)
1882 ,(compute-delta)))
1883 #-compare-and-swap-vops
1884 (with-unique-names (structure old-value)
1885 `(without-interrupts
1886 (let* ((,structure ,@args)
1887 (,old-value (,op ,structure)))
1888 (setf (,op ,structure) ,(compute-newval old-value))
1889 ,old-value)))))))))
1891 (sb-xc:defmacro atomic-incf (&environment env place &optional (diff 1))
1892 #.(format nil
1893 "Atomically increments PLACE by DIFF, and returns the value of PLACE before
1894 the increment.
1896 PLACE must access one of the following:
1897 - a DEFSTRUCT slot with declared type (UNSIGNED-BYTE ~D~:*)
1898 or AREF of a (SIMPLE-ARRAY (UNSIGNED-BYTE ~D~:*) (*))
1899 The type SB-EXT:WORD can be used for these purposes.
1900 - CAR or CDR (respectively FIRST or REST) of a CONS.
1901 - a variable defined using DEFGLOBAL with a proclaimed type of FIXNUM.
1902 Macroexpansion is performed on PLACE before expanding ATOMIC-INCF.
1904 Incrementing is done using modular arithmetic,
1905 which is well-defined over two different domains:
1906 - For structures and arrays, the operation accepts and produces
1907 an (UNSIGNED-BYTE ~D~:*), and DIFF must be of type (SIGNED-BYTE ~D).
1908 ATOMIC-INCF of #x~x by one results in #x0 being stored in PLACE.
1909 - For other places, the domain is FIXNUM, and DIFF must be a FIXNUM.
1910 ATOMIC-INCF of #x~x by one results in #x~x
1911 being stored in PLACE.
1913 DIFF defaults to 1.
1915 EXPERIMENTAL: Interface subject to change."
1916 sb-vm:n-word-bits most-positive-word
1917 most-positive-fixnum most-negative-fixnum)
1918 (expand-atomic-frob 'atomic-incf place diff env))
1920 (sb-xc:defmacro atomic-decf (&environment env place &optional (diff 1))
1921 #.(format nil
1922 "Atomically decrements PLACE by DIFF, and returns the value of PLACE before
1923 the decrement.
1925 PLACE must access one of the following:
1926 - a DEFSTRUCT slot with declared type (UNSIGNED-BYTE ~D~:*)
1927 or AREF of a (SIMPLE-ARRAY (UNSIGNED-BYTE ~D~:*) (*))
1928 The type SB-EXT:WORD can be used for these purposes.
1929 - CAR or CDR (respectively FIRST or REST) of a CONS.
1930 - a variable defined using DEFGLOBAL with a proclaimed type of FIXNUM.
1931 Macroexpansion is performed on PLACE before expanding ATOMIC-DECF.
1933 Decrementing is done using modular arithmetic,
1934 which is well-defined over two different domains:
1935 - For structures and arrays, the operation accepts and produces
1936 an (UNSIGNED-BYTE ~D~:*), and DIFF must be of type (SIGNED-BYTE ~D).
1937 ATOMIC-DECF of #x0 by one results in #x~x being stored in PLACE.
1938 - For other places, the domain is FIXNUM, and DIFF must be a FIXNUM.
1939 ATOMIC-DECF of #x~x by one results in #x~x
1940 being stored in PLACE.
1942 DIFF defaults to 1.
1944 EXPERIMENTAL: Interface subject to change."
1945 sb-vm:n-word-bits most-positive-word
1946 most-negative-fixnum most-positive-fixnum)
1947 (expand-atomic-frob 'atomic-decf place diff env))
1949 (sb-xc:defmacro atomic-update (place update-fn &rest arguments &environment env)
1950 "Updates PLACE atomically to the value returned by calling function
1951 designated by UPDATE-FN with ARGUMENTS and the previous value of PLACE.
1953 PLACE may be read and UPDATE-FN evaluated and called multiple times before the
1954 update succeeds: atomicity in this context means that the value of PLACE did
1955 not change between the time it was read, and the time it was replaced with the
1956 computed value.
1958 PLACE can be any place supported by SB-EXT:COMPARE-AND-SWAP.
1960 Examples:
1962 ;;; Conses T to the head of FOO-LIST.
1963 (defstruct foo list)
1964 (defvar *foo* (make-foo))
1965 (atomic-update (foo-list *foo*) #'cons t)
1967 (let ((x (cons :count 0)))
1968 (mapc #'sb-thread:join-thread
1969 (loop repeat 1000
1970 collect (sb-thread:make-thread
1971 (lambda ()
1972 (loop repeat 1000
1973 do (atomic-update (cdr x) #'1+)
1974 (sleep 0.00001))))))
1975 ;; Guaranteed to be (:COUNT . 1000000) -- if you replace
1976 ;; atomic update with (INCF (CDR X)) above, the result becomes
1977 ;; unpredictable.
1980 (multiple-value-bind (vars vals old new cas-form read-form)
1981 (get-cas-expansion place env)
1982 `(let* (,@(mapcar 'list vars vals)
1983 (,old ,read-form))
1984 (loop for ,new = (funcall ,update-fn ,@arguments ,old)
1985 until (eq ,old (setf ,old ,cas-form))
1986 finally (return ,new)))))
1988 (sb-xc:defmacro atomic-push (obj place &environment env)
1989 "Like PUSH, but atomic. PLACE may be read multiple times before
1990 the operation completes -- the write does not occur until such time
1991 that no other thread modified PLACE between the read and the write.
1993 Works on all CASable places."
1994 (multiple-value-bind (vars vals old new cas-form read-form)
1995 (get-cas-expansion place env)
1996 `(let* (,@(mapcar 'list vars vals)
1997 (,old ,read-form)
1998 (,new (cons ,obj ,old)))
1999 (loop until (eq ,old (setf ,old ,cas-form))
2000 do (setf (cdr ,new) ,old)
2001 finally (return ,new)))))
2003 (sb-xc:defmacro atomic-pop (place &environment env)
2004 "Like POP, but atomic. PLACE may be read multiple times before
2005 the operation completes -- the write does not occur until such time
2006 that no other thread modified PLACE between the read and the write.
2008 Works on all CASable places."
2009 (multiple-value-bind (vars vals old new cas-form read-form)
2010 (get-cas-expansion place env)
2011 `(let* (,@(mapcar 'list vars vals)
2012 (,old ,read-form))
2013 (loop (let ((,new (cdr ,old)))
2014 (when (eq ,old (setf ,old ,cas-form))
2015 (return (car (truly-the list ,old)))))))))