1 ;;;; various extensions (including SB-INT "internal extensions")
2 ;;;; available both in the cross-compilation host Lisp and in the
5 ;;;; This software is part of the SBCL system. See the README file for
8 ;;;; This software is derived from the CMU CL system, which was
9 ;;;; written at Carnegie Mellon University and released into the
10 ;;;; public domain. The software is in the public domain and is
11 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
12 ;;;; files for more information.
14 (in-package "SB!IMPL")
16 ;;; something not EQ to anything we might legitimately READ
17 (defparameter *eof-object
* (make-symbol "EOF-OBJECT"))
19 ;;; a type used for indexing into arrays, and for related quantities
20 ;;; like lengths of lists
22 ;;; It's intentionally limited to one less than the
23 ;;; ARRAY-DIMENSION-LIMIT for efficiency reasons, because in SBCL
24 ;;; ARRAY-DIMENSION-LIMIT is MOST-POSITIVE-FIXNUM, and staying below
25 ;;; that lets the system know it can increment a value of this type
26 ;;; without having to worry about using a bignum to represent the
29 ;;; (It should be safe to use ARRAY-DIMENSION-LIMIT as an exclusive
30 ;;; bound because ANSI specifies it as an exclusive bound.)
31 (def!type index
() `(integer 0 (,sb
!xc
:array-dimension-limit
)))
33 ;;; like INDEX, but only up to half the maximum. Used by hash-table
34 ;;; code that does plenty to (aref v (* 2 i)) and (aref v (1+ (* 2 i))).
35 (def!type index
/2 () `(integer 0 (,(floor sb
!xc
:array-dimension-limit
2))))
37 ;;; like INDEX, but augmented with -1 (useful when using the index
38 ;;; to count downwards to 0, e.g. LOOP FOR I FROM N DOWNTO 0, with
39 ;;; an implementation which terminates the loop by testing for the
40 ;;; index leaving the loop range)
41 (def!type index-or-minus-1
() `(integer -
1 (,sb
!xc
:array-dimension-limit
)))
43 ;;; A couple of VM-related types that are currently used only on the
44 ;;; alpha platform. -- CSR, 2002-06-24
45 (def!type unsigned-byte-with-a-bite-out
(s bite
)
46 (cond ((eq s
'*) 'integer
)
47 ((and (integerp s
) (> s
0))
48 (let ((bound (ash 1 s
)))
49 `(integer 0 ,(- bound bite
1))))
51 (error "Bad size specified for UNSIGNED-BYTE type specifier: ~S." s
))))
53 ;;; Motivated by the mips port. -- CSR, 2002-08-22
54 (def!type signed-byte-with-a-bite-out
(s bite
)
55 (cond ((eq s
'*) 'integer
)
56 ((and (integerp s
) (> s
1))
57 (let ((bound (ash 1 (1- s
))))
58 `(integer ,(- bound
) ,(- bound bite
1))))
60 (error "Bad size specified for SIGNED-BYTE type specifier: ~S." s
))))
62 (def!type load
/store-index
(scale lowtag min-offset
63 &optional
(max-offset min-offset
))
64 `(integer ,(- (truncate (+ (ash 1 16)
65 (* min-offset sb
!vm
:n-word-bytes
)
68 ,(truncate (- (+ (1- (ash 1 16)) lowtag
)
69 (* max-offset sb
!vm
:n-word-bytes
))
73 (defun displacement-bounds (lowtag element-size data-offset
)
74 (let* ((adjustment (- (* data-offset sb
!vm
:n-word-bytes
) lowtag
))
75 (bytes-per-element (ceiling element-size sb
!vm
:n-byte-bits
))
76 (min (truncate (+ sb
!vm
::minimum-immediate-offset adjustment
)
78 (max (truncate (+ sb
!vm
::maximum-immediate-offset adjustment
)
83 (def!type constant-displacement
(lowtag element-size data-offset
)
84 (flet ((integerify (x)
87 (symbol (symbol-value x
)))))
88 (let ((lowtag (integerify lowtag
))
89 (element-size (integerify element-size
))
90 (data-offset (integerify data-offset
)))
91 (multiple-value-bind (min max
) (displacement-bounds lowtag
94 `(integer ,min
,max
)))))
96 ;;; Similar to FUNCTION, but the result type is "exactly" specified:
97 ;;; if it is an object type, then the function returns exactly one
98 ;;; value, if it is a short form of VALUES, then this short form
99 ;;; specifies the exact number of values.
100 (def!type sfunction
(args &optional result
)
101 (let ((result (cond ((eq result
'*) '*)
103 (not (eq (car result
) 'values
)))
104 `(values ,result
&optional
))
105 ((intersection (cdr result
) lambda-list-keywords
)
107 (t `(values ,@(cdr result
) &optional
)))))
108 `(function ,args
,result
)))
112 ;;; FIXME: The SB!KERNEL:INSTANCE here really means CL:CLASS.
113 ;;; However, the CL:CLASS type is only defined once PCL is loaded,
114 ;;; which is before this is evaluated. Once PCL is moved into cold
115 ;;; init, this might be fixable.
116 (def!type type-specifier
() '(or list symbol sb
!kernel
:instance
))
118 ;;; the default value used for initializing character data. The ANSI
119 ;;; spec says this is arbitrary, so we use the value that falls
120 ;;; through when we just let the low-level consing code initialize
121 ;;; all newly-allocated memory to zero.
123 ;;; KLUDGE: It might be nice to use something which is a
124 ;;; STANDARD-CHAR, both to reduce user surprise a little and, probably
125 ;;; more significantly, to help SBCL's cross-compiler (which knows how
126 ;;; to dump STANDARD-CHARs). Unfortunately, the old CMU CL code is
127 ;;; shot through with implicit assumptions that it's #\NULL, and code
128 ;;; in several places (notably both DEFUN MAKE-ARRAY and DEFTRANSFORM
129 ;;; MAKE-ARRAY) would have to be rewritten. -- WHN 2001-10-04
130 (eval-when (:compile-toplevel
:load-toplevel
:execute
)
131 ;; an expression we can use to construct a DEFAULT-INIT-CHAR value
132 ;; at load time (so that we don't need to teach the cross-compiler
133 ;; how to represent and dump non-STANDARD-CHARs like #\NULL)
134 (defparameter *default-init-char-form
* '(code-char 0)))
136 ;;; CHAR-CODE values for ASCII characters which we care about but
137 ;;; which aren't defined in section "2.1.3 Standard Characters" of the
138 ;;; ANSI specification for Lisp
140 ;;; KLUDGE: These are typically used in the idiom (CODE-CHAR
141 ;;; FOO-CHAR-CODE). I suspect that the current implementation is
142 ;;; expanding this idiom into a full call to CODE-CHAR, which is an
143 ;;; annoying overhead. I should check whether this is happening, and
144 ;;; if so, perhaps implement a DEFTRANSFORM or something to stop it.
145 ;;; (or just find a nicer way of expressing characters portably?) --
147 (def!constant bell-char-code
7)
148 (def!constant backspace-char-code
8)
149 (def!constant tab-char-code
9)
150 (def!constant line-feed-char-code
10)
151 (def!constant form-feed-char-code
12)
152 (def!constant return-char-code
13)
153 (def!constant escape-char-code
27)
154 (def!constant rubout-char-code
127)
156 ;;;; type-ish predicates
158 ;;; X may contain cycles -- a conservative approximation. This
159 ;;; occupies a somewhat uncomfortable niche between being fast for
160 ;;; common cases (we don't want to allocate a hash-table), and not
161 ;;; falling down to exponential behaviour for large trees (so we set
162 ;;; an arbitrady depth limit beyond which we punt).
163 (defun maybe-cyclic-p (x &optional
(depth-limit 12))
165 (labels ((safe-cddr (cons)
166 (let ((cdr (cdr cons
)))
169 (check-cycle (object seen depth
)
170 (when (and (consp object
)
171 (or (> depth depth-limit
)
173 (circularp object seen depth
)))
174 (return-from maybe-cyclic-p t
)))
175 (circularp (list seen depth
)
176 ;; Almost regular circular list detection, with a twist:
177 ;; we also check each element of the list for upward
178 ;; references using CHECK-CYCLE.
179 (do ((fast (cons (car list
) (cdr list
)) (safe-cddr fast
))
180 (slow list
(cdr slow
)))
182 ;; Not CDR-circular, need to check remaining CARs yet
183 (do ((tail slow
(and (cdr tail
))))
186 (check-cycle (car tail
) (cons tail seen
) (1+ depth
))))
187 (check-cycle (car slow
) (cons slow seen
) (1+ depth
))
190 (circularp x
(list x
) 0))))
192 ;;; Is X a (possibly-improper) list of at least N elements?
193 (declaim (ftype (function (t index
)) list-of-length-at-least-p
))
194 (defun list-of-length-at-least-p (x n
)
195 (or (zerop n
) ; since anything can be considered an improper list of length 0
197 (list-of-length-at-least-p (cdr x
) (1- n
)))))
199 (declaim (inline singleton-p
))
200 (defun singleton-p (list)
204 ;;; Is X is a positive prime integer?
205 (defun positive-primep (x)
206 ;; This happens to be called only from one place in sbcl-0.7.0, and
207 ;; only for fixnums, we can limit it to fixnums for efficiency. (And
208 ;; if we didn't limit it to fixnums, we should use a cleverer
209 ;; algorithm, since this one scales pretty badly for huge X.)
212 (and (>= x
2) (/= x
4))
214 (not (zerop (rem x
3)))
217 (inc 2 (logxor inc
6)) ;; 2,4,2,4...
219 ((or (= r
0) (> d q
)) (/= r
0))
220 (declare (fixnum inc
))
221 (multiple-value-setq (q r
) (truncate x d
))))))
223 ;;; Could this object contain other objects? (This is important to
224 ;;; the implementation of things like *PRINT-CIRCLE* and the dumper.)
225 (defun compound-object-p (x)
228 (typep x
'(array t
*))))
230 ;;;; the COLLECT macro
232 ;;;; comment from CMU CL: "the ultimate collection macro..."
234 ;;; helper functions for COLLECT, which become the expanders of the
235 ;;; MACROLET definitions created by COLLECT
237 ;;; COLLECT-NORMAL-EXPANDER handles normal collection macros.
239 ;;; COLLECT-LIST-EXPANDER handles the list collection case. N-TAIL
240 ;;; is the pointer to the current tail of the list, or NIL if the list
242 (eval-when (#-sb-xc
:compile-toplevel
:load-toplevel
:execute
)
243 (defun collect-normal-expander (n-value fun forms
)
245 ,@(mapcar (lambda (form) `(setq ,n-value
(,fun
,form
,n-value
))) forms
)
247 (defun collect-list-expander (n-value n-tail forms
)
248 (let ((n-res (gensym)))
250 ,@(mapcar (lambda (form)
251 `(let ((,n-res
(cons ,form nil
)))
253 (setf (cdr ,n-tail
) ,n-res
)
254 (setq ,n-tail
,n-res
))
256 (setq ,n-tail
,n-res
,n-value
,n-res
)))))
260 ;;; Collect some values somehow. Each of the collections specifies a
261 ;;; bunch of things which collected during the evaluation of the body
262 ;;; of the form. The name of the collection is used to define a local
263 ;;; macro, a la MACROLET. Within the body, this macro will evaluate
264 ;;; each of its arguments and collect the result, returning the
265 ;;; current value after the collection is done. The body is evaluated
266 ;;; as a PROGN; to get the final values when you are done, just call
267 ;;; the collection macro with no arguments.
269 ;;; INITIAL-VALUE is the value that the collection starts out with,
270 ;;; which defaults to NIL. FUNCTION is the function which does the
271 ;;; collection. It is a function which will accept two arguments: the
272 ;;; value to be collected and the current collection. The result of
273 ;;; the function is made the new value for the collection. As a
274 ;;; totally magical special-case, FUNCTION may be COLLECT, which tells
275 ;;; us to build a list in forward order; this is the default. If an
276 ;;; INITIAL-VALUE is supplied for COLLECT, the stuff will be RPLACD'd
277 ;;; onto the end. Note that FUNCTION may be anything that can appear
278 ;;; in the functional position, including macros and lambdas.
279 (defmacro collect
(collections &body body
)
282 (dolist (spec collections
)
283 (unless (proper-list-of-length-p spec
1 3)
284 (error "malformed collection specifier: ~S" spec
))
285 (let* ((name (first spec
))
286 (default (second spec
))
287 (kind (or (third spec
) 'collect
))
288 (n-value (gensym (concatenate 'string
291 (push `(,n-value
,default
) binds
)
292 (if (eq kind
'collect
)
293 (let ((n-tail (gensym (concatenate 'string
297 (push `(,n-tail
(last ,n-value
)) binds
)
299 (push `(,name
(&rest args
)
300 (collect-list-expander ',n-value
',n-tail args
))
302 (push `(,name
(&rest args
)
303 (collect-normal-expander ',n-value
',kind args
))
305 `(macrolet ,macros
(let* ,(nreverse binds
) ,@body
))))
307 ;;;; some old-fashioned functions. (They're not just for old-fashioned
308 ;;;; code, they're also used as optimized forms of the corresponding
309 ;;;; general functions when the compiler can prove that they're
312 ;;; like (MEMBER ITEM LIST :TEST #'EQ)
313 (defun memq (item list
)
315 "Return tail of LIST beginning with first element EQ to ITEM."
316 ;; KLUDGE: These could be and probably should be defined as
317 ;; (MEMBER ITEM LIST :TEST #'EQ)),
318 ;; but when I try to cross-compile that, I get an error from
319 ;; LTN-ANALYZE-KNOWN-CALL, "Recursive known function definition". The
320 ;; comments for that error say it "is probably a botched interpreter stub".
321 ;; Rather than try to figure that out, I just rewrote this function from
322 ;; scratch. -- WHN 19990512
323 (do ((i list
(cdr i
)))
325 (when (eq (car i
) item
)
328 ;;; like (ASSOC ITEM ALIST :TEST #'EQ):
329 ;;; Return the first pair of ALIST where ITEM is EQ to the key of
331 (defun assq (item alist
)
332 ;; KLUDGE: CMU CL defined this with
333 ;; (DECLARE (INLINE ASSOC))
334 ;; (ASSOC ITEM ALIST :TEST #'EQ))
335 ;; which is pretty, but which would have required adding awkward
336 ;; build order constraints on SBCL (or figuring out some way to make
337 ;; inline definitions installable at build-the-cross-compiler time,
338 ;; which was too ambitious for now). Rather than mess with that, we
339 ;; just define ASSQ explicitly in terms of more primitive
342 ;; though it may look more natural to write this as
343 ;; (AND PAIR (EQ (CAR PAIR) ITEM))
344 ;; the temptation to do so should be resisted, as pointed out by PFD
345 ;; sbcl-devel 2003-08-16, as NIL elements are rare in association
346 ;; lists. -- CSR, 2003-08-16
347 (when (and (eq (car pair
) item
) (not (null pair
)))
350 ;;; like (DELETE .. :TEST #'EQ):
351 ;;; Delete all LIST entries EQ to ITEM (destructively modifying
352 ;;; LIST), and return the modified LIST.
353 (defun delq (item list
)
355 (do ((x list
(cdr x
))
358 (cond ((eq item
(car x
))
361 (rplacd splice
(cdr x
))))
362 (t (setq splice x
)))))) ; Move splice along to include element.
365 ;;; like (POSITION .. :TEST #'EQ):
366 ;;; Return the position of the first element EQ to ITEM.
367 (defun posq (item list
)
368 (do ((i list
(cdr i
))
371 (when (eq (car i
) item
)
374 (declaim (inline neq
))
378 ;;; not really an old-fashioned function, but what the calling
379 ;;; convention should've been: like NTH, but with the same argument
380 ;;; order as in all the other indexed dereferencing functions, with
381 ;;; the collection first and the index second
382 (declaim (inline nth-but-with-sane-arg-order
))
383 (declaim (ftype (function (list index
) t
) nth-but-with-sane-arg-order
))
384 (defun nth-but-with-sane-arg-order (list index
)
387 (defun adjust-list (list length initial-element
)
388 (let ((old-length (length list
)))
389 (cond ((< old-length length
)
390 (append list
(make-list (- length old-length
)
391 :initial-element initial-element
)))
392 ((> old-length length
)
393 (subseq list
0 length
))
396 ;;;; miscellaneous iteration extensions
398 ;;; like Scheme's named LET
400 ;;; (CMU CL called this ITERATE, and commented it as "the ultimate
401 ;;; iteration macro...". I (WHN) found the old name insufficiently
402 ;;; specific to remind me what the macro means, so I renamed it.)
403 (defmacro named-let
(name binds
&body body
)
405 (unless (proper-list-of-length-p x
2)
406 (error "malformed NAMED-LET variable spec: ~S" x
)))
407 `(labels ((,name
,(mapcar #'first binds
) ,@body
))
408 (,name
,@(mapcar #'second binds
))))
410 (defun filter-dolist-declarations (decls)
411 (mapcar (lambda (decl)
412 `(declare ,@(remove-if
415 (or (eq (car clause
) 'type
)
416 (eq (car clause
) 'ignore
))))
420 ;;; just like DOLIST, but with one-dimensional arrays
421 (defmacro dovector
((elt vector
&optional result
) &body body
)
422 (multiple-value-bind (forms decls
) (parse-body body
:doc-string-allowed nil
)
423 (with-unique-names (index length vec
)
424 `(let ((,vec
,vector
))
425 (declare (type vector
,vec
))
426 (do ((,index
0 (1+ ,index
))
427 (,length
(length ,vec
)))
428 ((>= ,index
,length
) (let ((,elt nil
))
429 ,@(filter-dolist-declarations decls
)
432 (let ((,elt
(aref ,vec
,index
)))
437 ;;; Iterate over the entries in a HASH-TABLE, first obtaining the lock
438 ;;; if the table is a synchronized table.
439 (defmacro dohash
(((key-var value-var
) table
&key result locked
) &body body
)
440 (multiple-value-bind (forms decls
) (parse-body body
:doc-string-allowed nil
)
441 (let* ((gen (gensym))
444 (iter-form `(with-hash-table-iterator (,gen
,n-table
)
446 (multiple-value-bind (,n-more
,key-var
,value-var
) (,gen
)
448 (unless ,n-more
(return ,result
))
450 `(let ((,n-table
,table
))
452 `(with-locked-hash-table (,n-table
)
456 ;;;; hash cache utility
458 (eval-when (:compile-toplevel
:load-toplevel
:execute
)
459 (defvar *profile-hash-cache
* nil
))
461 ;;; a flag for whether it's too early in cold init to use caches so
462 ;;; that we have a better chance of recovering so that we have a
463 ;;; better chance of getting the system running so that we have a
464 ;;; better chance of diagnosing the problem which caused us to use the
467 (defvar *hash-caches-initialized-p
*)
469 ;;; Define a hash cache that associates some number of argument values
470 ;;; with a result value. The TEST-FUNCTION paired with each ARG-NAME
471 ;;; is used to compare the value for that arg in a cache entry with a
472 ;;; supplied arg. The TEST-FUNCTION must not error when passed NIL as
473 ;;; its first arg, but need not return any particular value.
474 ;;; TEST-FUNCTION may be any thing that can be placed in CAR position.
476 ;;; This code used to store all the arguments / return values directly
477 ;;; in the cache vector. This was both interrupt- and thread-unsafe, since
478 ;;; it was possible that *-CACHE-ENTER would scribble over a region of the
479 ;;; cache vector which *-CACHE-LOOKUP had only partially processed. Instead
480 ;;; we now store the contents of each cache bucket as a separate array, which
481 ;;; is stored in the appropriate cell in the cache vector. A new bucket array
482 ;;; is created every time *-CACHE-ENTER is called, and the old ones are never
483 ;;; modified. This means that *-CACHE-LOOKUP will always work with a set
484 ;;; of consistent data. The overhead caused by consing new buckets seems to
485 ;;; be insignificant on the grand scale of things. -- JES, 2006-11-02
487 ;;; NAME is used to define these functions:
488 ;;; <name>-CACHE-LOOKUP Arg*
489 ;;; See whether there is an entry for the specified ARGs in the
490 ;;; cache. If not present, the :DEFAULT keyword (default NIL)
491 ;;; determines the result(s).
492 ;;; <name>-CACHE-ENTER Arg* Value*
493 ;;; Encache the association of the specified args with VALUE.
494 ;;; <name>-CACHE-CLEAR
495 ;;; Reinitialize the cache, invalidating all entries and allowing
496 ;;; the arguments and result values to be GC'd.
498 ;;; These other keywords are defined:
500 ;;; The size of the cache as a power of 2.
501 ;;; :HASH-FUNCTION function
502 ;;; Some thing that can be placed in CAR position which will compute
503 ;;; a value between 0 and (1- (expt 2 <hash-bits>)).
505 ;;; the number of return values cached for each function call
506 ;;; :INIT-WRAPPER <name>
507 ;;; The code for initializing the cache is wrapped in a form with
508 ;;; the specified name. (:INIT-WRAPPER is set to COLD-INIT-FORMS
509 ;;; in type system definitions so that caches will be created
510 ;;; before top level forms run.)
511 (defmacro define-hash-cache
(name args
&key hash-function hash-bits default
512 (init-wrapper 'progn
)
514 (let* ((var-name (symbolicate "*" name
"-CACHE-VECTOR*"))
515 (nargs (length args
))
516 (size (ash 1 hash-bits
))
517 (default-values (if (and (consp default
) (eq (car default
) 'values
))
520 (args-and-values (gensym))
521 (args-and-values-size (+ nargs values
))
525 (unless (= (length default-values
) values
)
526 (error "The number of default values ~S differs from :VALUES ~W."
538 (let ((name (gensym)))
540 (values-refs `(svref ,args-and-values
(+ ,nargs
,i
)))
541 (sets `(setf (svref ,args-and-values
(+ ,nargs
,i
)) ,name
))))
544 (unless (= (length arg
) 2)
545 (error "bad argument spec: ~S" arg
))
546 (let ((arg-name (first arg
))
549 (tests `(,test
(svref ,args-and-values
,n
) ,arg-name
))
550 (sets `(setf (svref ,args-and-values
,n
) ,arg-name
)))
553 (when *profile-hash-cache
*
554 (let ((n-probe (symbolicate "*" name
"-CACHE-PROBES*"))
555 (n-miss (symbolicate "*" name
"-CACHE-MISSES*")))
556 (inits `(setq ,n-probe
0))
557 (inits `(setq ,n-miss
0))
558 (forms `(defvar ,n-probe
))
559 (forms `(defvar ,n-miss
))
560 (forms `(declaim (fixnum ,n-miss
,n-probe
)))))
562 (let ((fun-name (symbolicate name
"-CACHE-LOOKUP")))
565 `(defun ,fun-name
,(arg-vars)
566 ,@(when *profile-hash-cache
*
567 `((incf ,(symbolicate "*" name
"-CACHE-PROBES*"))))
568 (let* ((,n-index
(,hash-function
,@(arg-vars)))
570 (,args-and-values
(svref ,n-cache
,n-index
)))
571 (cond ((and ,args-and-values
573 (values ,@(values-refs)))
575 ,@(when *profile-hash-cache
*
576 `((incf ,(symbolicate "*" name
"-CACHE-MISSES*"))))
579 (let ((fun-name (symbolicate name
"-CACHE-ENTER")))
582 `(defun ,fun-name
(,@(arg-vars) ,@(values-names))
583 (let ((,n-index
(,hash-function
,@(arg-vars)))
585 (,args-and-values
(make-array ,args-and-values-size
)))
587 (setf (svref ,n-cache
,n-index
) ,args-and-values
))
590 (let ((fun-name (symbolicate name
"-CACHE-CLEAR")))
593 (fill ,var-name nil
)))
594 (forms `(,fun-name
)))
596 (inits `(unless (boundp ',var-name
)
597 (setq ,var-name
(make-array ,size
:initial-element nil
))))
598 #!+sb-show
(inits `(setq *hash-caches-initialized-p
* t
))
602 (declaim (type (simple-vector ,size
) ,var-name
))
603 #!-sb-fluid
(declaim (inline ,@(inlines)))
604 (,init-wrapper
,@(inits))
608 ;;; some syntactic sugar for defining a function whose values are
609 ;;; cached by DEFINE-HASH-CACHE
610 (defmacro defun-cached
((name &rest options
&key
(values 1) default
612 args
&body body-decls-doc
)
613 (let ((default-values (if (and (consp default
) (eq (car default
) 'values
))
616 (arg-names (mapcar #'car args
)))
617 (collect ((values-names))
619 (values-names (gensym)))
620 (multiple-value-bind (body decls doc
) (parse-body body-decls-doc
)
622 (define-hash-cache ,name
,args
,@options
)
623 (defun ,name
,arg-names
627 ((not (boundp '*hash-caches-initialized-p
*))
628 ;; This shouldn't happen, but it did happen to me
629 ;; when revising the type system, and it's a lot
630 ;; easier to figure out what what's going on with
631 ;; that kind of problem if the system can be kept
632 ;; alive until cold boot is complete. The recovery
633 ;; mechanism should definitely be conditional on
634 ;; some debugging feature (e.g. SB-SHOW) because
635 ;; it's big, duplicating all the BODY code. -- WHN
636 (/show0
,name
" too early in cold init, uncached")
637 (/show0
,(first arg-names
) "=..")
638 (/hexstr
,(first arg-names
))
641 (multiple-value-bind ,(values-names)
642 (,(symbolicate name
"-CACHE-LOOKUP") ,@arg-names
)
643 (if (and ,@(mapcar (lambda (val def
)
645 (values-names) default-values
))
646 (multiple-value-bind ,(values-names)
648 (,(symbolicate name
"-CACHE-ENTER") ,@arg-names
650 (values ,@(values-names)))
651 (values ,@(values-names))))))))))))
653 (defmacro define-cached-synonym
654 (name &optional
(original (symbolicate "%" name
)))
655 (let ((cached-name (symbolicate "%%" name
"-CACHED")))
657 (defun-cached (,cached-name
:hash-bits
8
658 :hash-function
(lambda (x)
659 (logand (sxhash x
) #xff
)))
661 (apply #',original args
))
662 (defun ,name
(&rest args
)
663 (,cached-name args
)))))
665 ;;; FIXME: maybe not the best place
667 ;;; FIXME: think of a better name -- not only does this not have the
668 ;;; CAR recursion of EQUAL, it also doesn't have the special treatment
669 ;;; of pathnames, bit-vectors and strings.
671 ;;; KLUDGE: This means that we will no longer cache specifiers of the
672 ;;; form '(INTEGER (0) 4). This is probably not a disaster.
674 ;;; A helper function for the type system, which is the main user of
675 ;;; these caches: we must be more conservative than EQUAL for some of
676 ;;; our equality tests, because MEMBER and friends refer to EQLity.
678 (defun equal-but-no-car-recursion (x y
)
683 (eql (car x
) (car y
))
684 (equal-but-no-car-recursion (cdr x
) (cdr y
))))
689 ;;; Note: Almost always you want to use FIND-UNDELETED-PACKAGE-OR-LOSE
690 ;;; instead of this function. (The distinction only actually matters when
691 ;;; PACKAGE-DESIGNATOR is actually a deleted package, and in that case
692 ;;; you generally do want to signal an error instead of proceeding.)
693 (defun %find-package-or-lose
(package-designator)
694 (or (find-package package-designator
)
695 (error 'sb
!kernel
:simple-package-error
696 :package package-designator
697 :format-control
"The name ~S does not designate any package."
698 :format-arguments
(list package-designator
))))
700 ;;; ANSI specifies (in the section for FIND-PACKAGE) that the
701 ;;; consequences of most operations on deleted packages are
702 ;;; unspecified. We try to signal errors in such cases.
703 (defun find-undeleted-package-or-lose (package-designator)
704 (let ((maybe-result (%find-package-or-lose package-designator
)))
705 (if (package-name maybe-result
) ; if not deleted
707 (error 'sb
!kernel
:simple-package-error
708 :package maybe-result
709 :format-control
"The package ~S has been deleted."
710 :format-arguments
(list maybe-result
)))))
712 ;;;; various operations on names
714 ;;; Is NAME a legal function name?
715 (declaim (inline legal-fun-name-p
))
716 (defun legal-fun-name-p (name)
717 (values (valid-function-name-p name
)))
719 (deftype function-name
() '(satisfies legal-fun-name-p
))
721 ;;; Signal an error unless NAME is a legal function name.
722 (defun legal-fun-name-or-type-error (name)
723 (unless (legal-fun-name-p name
)
724 (error 'simple-type-error
726 :expected-type
'function-name
727 :format-control
"invalid function name: ~S"
728 :format-arguments
(list name
))))
730 ;;; Given a function name, return the symbol embedded in it.
732 ;;; The ordinary use for this operator (and the motivation for the
733 ;;; name of this operator) is to convert from a function name to the
734 ;;; name of the BLOCK which encloses its body.
736 ;;; Occasionally the operator is useful elsewhere, where the operator
737 ;;; name is less mnemonic. (Maybe it should be changed?)
738 (declaim (ftype (function ((or symbol cons
)) symbol
) fun-name-block-name
))
739 (defun fun-name-block-name (fun-name)
740 (cond ((symbolp fun-name
)
743 (multiple-value-bind (legalp block-name
)
744 (valid-function-name-p fun-name
)
747 (error "not legal as a function name: ~S" fun-name
))))
749 (error "not legal as a function name: ~S" fun-name
))))
751 (defun looks-like-name-of-special-var-p (x)
753 (let ((name (symbol-name x
)))
754 (and (> (length name
) 2) ; to exclude '* and '**
755 (char= #\
* (aref name
0))
756 (char= #\
* (aref name
(1- (length name
))))))))
758 ;;; Some symbols are defined by ANSI to be self-evaluating. Return
759 ;;; non-NIL for such symbols (and make the non-NIL value a traditional
760 ;;; message, for use in contexts where the user asks us to change such
762 (defun symbol-self-evaluating-p (symbol)
763 (declare (type symbol symbol
))
765 "Veritas aeterna. (can't change T)")
767 "Nihil ex nihil. (can't change NIL)")
769 "Keyword values can't be changed.")
773 ;;; This function is to be called just before a change which would
774 ;;; affect the symbol value. (We don't absolutely have to call this
775 ;;; function before such changes, since such changes are given as
776 ;;; undefined behavior. In particular, we don't if the runtime cost
777 ;;; would be annoying. But otherwise it's nice to do so.)
778 (defun about-to-modify-symbol-value (symbol)
779 (declare (type symbol symbol
))
780 (let ((reason (symbol-self-evaluating-p symbol
)))
783 ;; (Note: Just because a value is CONSTANTP is not a good enough
784 ;; reason to complain here, because we want DEFCONSTANT to be able
785 ;; to use this function, and it's legal to DEFCONSTANT a constant as
786 ;; long as the new value is EQL to the old value.)
790 ;;; If COLD-FSET occurs not at top level, just treat it as an ordinary
791 ;;; assignment instead of doing cold static linking. That way things like
792 ;;; (FLET ((FROB (X) ..))
793 ;;; (DEFUN FOO (X Y) (FROB X) ..)
794 ;;; (DEFUN BAR (Z) (AND (FROB X) ..)))
795 ;;; can still "work" for cold init: they don't do magical static
796 ;;; linking the way that true toplevel DEFUNs do, but at least they do
797 ;;; the linking eventually, so as long as #'FOO and #'BAR aren't
798 ;;; needed until "cold toplevel forms" have executed, it's OK.
799 (defmacro cold-fset
(name lambda
)
801 "~@<COLD-FSET ~S not cross-compiled at top level: demoting to ~
802 (SETF FDEFINITION)~:@>"
804 ;; We convert the LAMBDA expression to the corresponding NAMED-LAMBDA
805 ;; expression so that the compiler can use NAME in debug names etc.
806 (destructuring-bind (lambda-symbol &rest lambda-rest
) lambda
807 (assert (eql lambda-symbol
'lambda
)) ; else dunno how to do conversion
808 `(setf (fdefinition ',name
)
809 (named-lambda ,name
,@lambda-rest
))))
813 ;;;; "The macro ONCE-ONLY has been around for a long time on various
814 ;;;; systems [..] if you can understand how to write and when to use
815 ;;;; ONCE-ONLY, then you truly understand macro." -- Peter Norvig,
816 ;;;; _Paradigms of Artificial Intelligence Programming: Case Studies
817 ;;;; in Common Lisp_, p. 853
819 ;;; ONCE-ONLY is a utility useful in writing source transforms and
820 ;;; macros. It provides a concise way to wrap a LET around some code
821 ;;; to ensure that some forms are only evaluated once.
823 ;;; Create a LET* which evaluates each value expression, binding a
824 ;;; temporary variable to the result, and wrapping the LET* around the
825 ;;; result of the evaluation of BODY. Within the body, each VAR is
826 ;;; bound to the corresponding temporary variable.
827 (defmacro once-only
(specs &body body
)
828 (named-let frob
((specs specs
)
832 (let ((spec (first specs
)))
833 ;; FIXME: should just be DESTRUCTURING-BIND of SPEC
834 (unless (proper-list-of-length-p spec
2)
835 (error "malformed ONCE-ONLY binding spec: ~S" spec
))
836 (let* ((name (first spec
))
837 (exp-temp (gensym (symbol-name name
))))
838 `(let ((,exp-temp
,(second spec
))
839 (,name
(gensym "ONCE-ONLY-")))
840 `(let ((,,name
,,exp-temp
))
841 ,,(frob (rest specs
) body
))))))))
843 ;;;; various error-checking utilities
845 ;;; This function can be used as the default value for keyword
846 ;;; arguments that must be always be supplied. Since it is known by
847 ;;; the compiler to never return, it will avoid any compile-time type
848 ;;; warnings that would result from a default value inconsistent with
849 ;;; the declared type. When this function is called, it signals an
850 ;;; error indicating that a required &KEY argument was not supplied.
851 ;;; This function is also useful for DEFSTRUCT slot defaults
852 ;;; corresponding to required arguments.
853 (declaim (ftype (function () nil
) missing-arg
))
854 (defun missing-arg ()
856 (/show0
"entering MISSING-ARG")
857 (error "A required &KEY or &OPTIONAL argument was not supplied."))
859 ;;; like CL:ASSERT and CL:CHECK-TYPE, but lighter-weight
861 ;;; (As of sbcl-0.6.11.20, we were using some 400 calls to CL:ASSERT.
862 ;;; The CL:ASSERT restarts and whatnot expand into a significant
863 ;;; amount of code when you multiply them by 400, so replacing them
864 ;;; with this should reduce the size of the system by enough to be
865 ;;; worthwhile. ENFORCE-TYPE is much less common, but might still be
866 ;;; worthwhile, and since I don't really like CERROR stuff deep in the
867 ;;; guts of complex systems anyway, I replaced it too.)
868 (defmacro aver
(expr)
870 (%failed-aver
,(format nil
"~A" expr
))))
872 (defun %failed-aver
(expr-as-string)
873 ;; hackish way to tell we're in a cold sbcl and output the
874 ;; message before signallign error, as it may be this is too
875 ;; early in the cold init.
876 (when (find-package "SB!C")
878 (write-line "failed AVER:")
879 (write-line expr-as-string
)
881 (bug "~@<failed AVER: ~2I~_~S~:>" expr-as-string
))
883 (defun bug (format-control &rest format-arguments
)
885 :format-control format-control
886 :format-arguments format-arguments
))
888 (defmacro enforce-type
(value type
)
889 (once-only ((value value
))
890 `(unless (typep ,value
',type
)
891 (%failed-enforce-type
,value
',type
))))
893 (defun %failed-enforce-type
(value type
)
894 ;; maybe should be TYPE-BUG, subclass of BUG? If it is changed,
895 ;; check uses of it in user-facing code (e.g. WARN)
896 (error 'simple-type-error
899 :format-control
"~@<~S ~_is not a ~_~S~:>"
900 :format-arguments
(list value type
)))
902 ;;; Return a function like FUN, but expecting its (two) arguments in
903 ;;; the opposite order that FUN does.
904 (declaim (inline swapped-args-fun
))
905 (defun swapped-args-fun (fun)
906 (declare (type function fun
))
910 ;;; Return the numeric value of a type bound, i.e. an interval bound
911 ;;; more or less in the format of bounds in ANSI's type specifiers,
912 ;;; where a bare numeric value is a closed bound and a list of a
913 ;;; single numeric value is an open bound.
915 ;;; The "more or less" bit is that the no-bound-at-all case is
916 ;;; represented by NIL (not by * as in ANSI type specifiers); and in
917 ;;; this case we return NIL.
918 (defun type-bound-number (x)
920 (destructuring-bind (result) x result
)
923 ;;; some commonly-occuring CONSTANTLY forms
924 (macrolet ((def-constantly-fun (name constant-expr
)
925 `(setf (symbol-function ',name
)
926 (constantly ,constant-expr
))))
927 (def-constantly-fun constantly-t t
)
928 (def-constantly-fun constantly-nil nil
)
929 (def-constantly-fun constantly-0
0))
931 ;;; If X is a symbol, see whether it is present in *FEATURES*. Also
932 ;;; handle arbitrary combinations of atoms using NOT, AND, OR.
940 (error "too many subexpressions in feature expression: ~S" x
))
942 (error "too few subexpressions in feature expression: ~S" x
))
943 (t (not (featurep (cadr x
))))))
944 ((:and and
) (every #'featurep
(cdr x
)))
945 ((:or or
) (some #'featurep
(cdr x
)))
947 (error "unknown operator in feature expression: ~S." x
))))
948 (symbol (not (null (memq x
*features
*))))))
950 ;;;; utilities for two-VALUES predicates
952 (defmacro not
/type
(x)
953 (let ((val (gensym "VAL"))
954 (win (gensym "WIN")))
955 `(multiple-value-bind (,val
,win
)
958 (values (not ,val
) t
)
961 (defmacro and
/type
(x y
)
962 `(multiple-value-bind (val1 win1
) ,x
963 (if (and (not val1
) win1
)
965 (multiple-value-bind (val2 win2
) ,y
968 (values nil
(and win2
(not val2
))))))))
970 ;;; sort of like ANY and EVERY, except:
971 ;;; * We handle two-VALUES predicate functions, as SUBTYPEP does.
972 ;;; (And if the result is uncertain, then we return (VALUES NIL NIL),
973 ;;; as SUBTYPEP does.)
974 ;;; * THING is just an atom, and we apply OP (an arity-2 function)
975 ;;; successively to THING and each element of LIST.
976 (defun any/type
(op thing list
)
977 (declare (type function op
))
979 (dolist (i list
(values nil certain?
))
980 (multiple-value-bind (sub-value sub-certain?
) (funcall op thing i
)
982 (when sub-value
(return (values t t
)))
983 (setf certain? nil
))))))
984 (defun every/type
(op thing list
)
985 (declare (type function op
))
987 (dolist (i list
(if certain?
(values t t
) (values nil nil
)))
988 (multiple-value-bind (sub-value sub-certain?
) (funcall op thing i
)
990 (unless sub-value
(return (values nil t
)))
991 (setf certain? nil
))))))
995 ;;; These functions are called by the expansion of the DEFPRINTER
996 ;;; macro to do the actual printing.
997 (declaim (ftype (function (symbol t stream
) (values))
998 defprinter-prin1 defprinter-princ
))
999 (defun defprinter-prin1 (name value stream
)
1000 (defprinter-prinx #'prin1 name value stream
))
1001 (defun defprinter-princ (name value stream
)
1002 (defprinter-prinx #'princ name value stream
))
1003 (defun defprinter-prinx (prinx name value stream
)
1004 (declare (type function prinx
))
1005 (when *print-pretty
*
1006 (pprint-newline :linear stream
))
1007 (format stream
":~A " name
)
1008 (funcall prinx value stream
)
1010 (defun defprinter-print-space (stream)
1011 (write-char #\space stream
))
1013 ;;; Define some kind of reasonable PRINT-OBJECT method for a
1014 ;;; STRUCTURE-OBJECT class.
1016 ;;; NAME is the name of the structure class, and CONC-NAME is the same
1017 ;;; as in DEFSTRUCT.
1019 ;;; The SLOT-DESCS describe how each slot should be printed. Each
1020 ;;; SLOT-DESC can be a slot name, indicating that the slot should
1021 ;;; simply be printed. A SLOT-DESC may also be a list of a slot name
1022 ;;; and other stuff. The other stuff is composed of keywords followed
1023 ;;; by expressions. The expressions are evaluated with the variable
1024 ;;; which is the slot name bound to the value of the slot. These
1025 ;;; keywords are defined:
1027 ;;; :PRIN1 Print the value of the expression instead of the slot value.
1028 ;;; :PRINC Like :PRIN1, only PRINC the value
1029 ;;; :TEST Only print something if the test is true.
1031 ;;; If no printing thing is specified then the slot value is printed
1034 ;;; The structure being printed is bound to STRUCTURE and the stream
1035 ;;; is bound to STREAM.
1036 (defmacro defprinter
((name
1038 (conc-name (concatenate 'simple-string
1045 (reversed-prints nil
)
1046 (stream (gensym "STREAM")))
1047 (flet ((sref (slot-name)
1048 `(,(symbolicate conc-name slot-name
) structure
)))
1049 (dolist (slot-desc slot-descs
)
1051 (setf maybe-print-space nil
1053 (setf maybe-print-space
`(defprinter-print-space ,stream
)))
1054 (cond ((atom slot-desc
)
1055 (push maybe-print-space reversed-prints
)
1056 (push `(defprinter-prin1 ',slot-desc
,(sref slot-desc
) ,stream
)
1059 (let ((sname (first slot-desc
))
1062 (do ((option (rest slot-desc
) (cddr option
)))
1064 (push `(let ((,sname
,(sref sname
)))
1069 ',sname
,sname
,stream
)))))
1071 (case (first option
)
1073 (stuff `(defprinter-prin1
1074 ',sname
,(second option
) ,stream
)))
1076 (stuff `(defprinter-princ
1077 ',sname
,(second option
) ,stream
)))
1078 (:test
(setq test
(second option
)))
1080 (error "bad option: ~S" (first option
)))))))))))
1081 `(def!method print-object
((structure ,name
) ,stream
)
1082 (pprint-logical-block (,stream nil
)
1083 (print-unreadable-object (structure
1086 :identity
,identity
)
1087 ,@(nreverse reversed-prints
))))))
1091 ;;; Given a pathname, return a corresponding physical pathname.
1092 (defun physicalize-pathname (possibly-logical-pathname)
1093 (if (typep possibly-logical-pathname
'logical-pathname
)
1094 (translate-logical-pathname possibly-logical-pathname
)
1095 possibly-logical-pathname
))
1097 (defun deprecation-warning (bad-name &optional good-name
)
1098 (warn "using deprecated ~S~@[, should use ~S instead~]"
1102 ;;; Anaphoric macros
1103 (defmacro awhen
(test &body body
)
1107 (defmacro acond
(&rest clauses
)
1110 (destructuring-bind ((test &body body
) &rest rest
) clauses
1111 (once-only ((test test
))
1113 (let ((it ,test
)) (declare (ignorable it
)),@body
)
1116 ;;; (binding* ({(names initial-value [flag])}*) body)
1117 ;;; FLAG may be NIL or :EXIT-IF-NULL
1119 ;;; This form unites LET*, MULTIPLE-VALUE-BIND and AWHEN.
1120 (defmacro binding
* ((&rest bindings
) &body body
)
1121 (let ((bindings (reverse bindings
)))
1122 (loop with form
= `(progn ,@body
)
1123 for binding in bindings
1124 do
(destructuring-bind (names initial-value
&optional flag
)
1126 (multiple-value-bind (names declarations
)
1129 (let ((name (gensym)))
1130 (values (list name
) `((declare (ignorable ,name
))))))
1132 (values (list names
) nil
))
1134 (collect ((new-names) (ignorable))
1135 (dolist (name names
)
1137 (setq name
(gensym))
1142 `((declare (ignorable ,@(ignorable)))))))))
1143 (setq form
`(multiple-value-bind ,names
1149 `(when ,(first names
) ,form
)))))))
1150 finally
(return form
))))
1152 ;;; Delayed evaluation
1153 (defmacro delay
(form)
1154 `(cons nil
(lambda () ,form
)))
1156 (defun force (promise)
1157 (cond ((not (consp promise
)) promise
)
1158 ((car promise
) (cdr promise
))
1159 (t (setf (car promise
) t
1160 (cdr promise
) (funcall (cdr promise
))))))
1162 (defun promise-ready-p (promise)
1163 (or (not (consp promise
))
1167 (defmacro with-rebound-io-syntax
(&body body
)
1168 `(%with-rebound-io-syntax
(lambda () ,@body
)))
1170 (defun %with-rebound-io-syntax
(function)
1171 (declare (type function function
))
1172 (let ((*package
* *package
*)
1173 (*print-array
* *print-array
*)
1174 (*print-base
* *print-base
*)
1175 (*print-case
* *print-case
*)
1176 (*print-circle
* *print-circle
*)
1177 (*print-escape
* *print-escape
*)
1178 (*print-gensym
* *print-gensym
*)
1179 (*print-length
* *print-length
*)
1180 (*print-level
* *print-level
*)
1181 (*print-lines
* *print-lines
*)
1182 (*print-miser-width
* *print-miser-width
*)
1183 (*print-pretty
* *print-pretty
*)
1184 (*print-radix
* *print-radix
*)
1185 (*print-readably
* *print-readably
*)
1186 (*print-right-margin
* *print-right-margin
*)
1187 (*read-base
* *read-base
*)
1188 (*read-default-float-format
* *read-default-float-format
*)
1189 (*read-eval
* *read-eval
*)
1190 (*read-suppress
* *read-suppress
*)
1191 (*readtable
* *readtable
*))
1192 (funcall function
)))
1194 ;;; Bind a few "potentially dangerous" printer control variables to
1195 ;;; safe values, respecting current values if possible.
1196 (defmacro with-sane-io-syntax
(&body forms
)
1197 `(call-with-sane-io-syntax (lambda () ,@forms
)))
1199 (defun call-with-sane-io-syntax (function)
1200 (declare (type function function
))
1201 (macrolet ((true (sym)
1202 `(and (boundp ',sym
) ,sym
)))
1203 (let ((*print-readably
* nil
)
1204 (*print-level
* (or (true *print-level
*) 6))
1205 (*print-length
* (or (true *print-length
*) 12)))
1206 (funcall function
))))
1208 ;;; Default evaluator mode (interpeter / compiler)
1210 (declaim (type (member :compile
#!+sb-eval
:interpret
) *evaluator-mode
*))
1211 (defparameter *evaluator-mode
* :compile
1213 "Toggle between different evaluator implementations. If set to :COMPILE,
1214 an implementation of EVAL that calls the compiler will be used. If set
1215 to :INTERPRET, an interpreter will be used.")
1217 ;;; Helper for making the DX closure allocation in macros expanding
1218 ;;; to CALL-WITH-FOO less ugly.
1220 ;;; This expands to something like
1222 ;;; (flet ((foo (...) <body-of-foo>))
1223 ;;; (declare (optimize stack-allocate-dynamic-extent))
1224 ;;; (flet ((foo (...)
1226 ;;; (declare (dynamic-extent #'foo))
1227 ;;; <body-of-dx-flet>)))
1229 ;;; The outer FLETs are inlined into the inner ones, and the inner ones
1230 ;;; are DX-allocated. The double-fletting is done to keep the bodies of
1231 ;;; the functions in an environment with correct policy: we don't want
1232 ;;; to force DX allocation in their bodies, which would be bad eg.
1234 (defmacro dx-flet
(functions &body forms
)
1235 (let ((names (mapcar #'car functions
)))
1238 (declare (optimize sb
!c
::stack-allocate-dynamic-extent
))
1241 (let ((args (cadr f
))
1243 (when (intersection args lambda-list-keywords
)
1244 ;; No fundamental reason not to support them, but we
1245 ;; don't currently need them here.
1246 (error "Non-required arguments not implemented for DX-FLET."))
1250 (declare (dynamic-extent ,@(mapcar (lambda (x) `(function ,x
)) names
)))
1253 ;;; Another similar one -- but actually touches the policy of the body,
1254 ;;; so take care with this one...
1255 (defmacro dx-let
(bindings &body forms
)
1258 (declare (optimize sb
!c
::stack-allocate-dynamic-extent
))
1260 (declare (dynamic-extent ,@(mapcar (lambda (bind)
1267 (in-package "SB!KERNEL")
1269 (defun fp-zero-p (x)
1271 (single-float (zerop x
))
1272 (double-float (zerop x
))
1274 (long-float (zerop x
))
1277 (defun neg-fp-zero (x)
1281 (make-unportable-float :single-float-negative-zero
)
1285 (make-unportable-float :double-float-negative-zero
)
1290 (make-unportable-float :long-float-negative-zero
)