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 (eval-when (:compile-toplevel
:load-toplevel
:execute
)
20 (defconstant max-hash sb
!xc
:most-positive-fixnum
))
23 `(integer 0 ,max-hash
))
25 ;;; a type used for indexing into arrays, and for related quantities
26 ;;; like lengths of lists
28 ;;; It's intentionally limited to one less than the
29 ;;; ARRAY-DIMENSION-LIMIT for efficiency reasons, because in SBCL
30 ;;; ARRAY-DIMENSION-LIMIT is MOST-POSITIVE-FIXNUM, and staying below
31 ;;; that lets the system know it can increment a value of this type
32 ;;; without having to worry about using a bignum to represent the
35 ;;; (It should be safe to use ARRAY-DIMENSION-LIMIT as an exclusive
36 ;;; bound because ANSI specifies it as an exclusive bound.)
37 (def!type index
() `(integer 0 (,sb
!xc
:array-dimension-limit
)))
39 ;;; like INDEX, but only up to half the maximum. Used by hash-table
40 ;;; code that does plenty to (aref v (* 2 i)) and (aref v (1+ (* 2 i))).
41 (def!type index
/2 () `(integer 0 (,(floor sb
!xc
:array-dimension-limit
2))))
43 ;;; like INDEX, but augmented with -1 (useful when using the index
44 ;;; to count downwards to 0, e.g. LOOP FOR I FROM N DOWNTO 0, with
45 ;;; an implementation which terminates the loop by testing for the
46 ;;; index leaving the loop range)
47 (def!type index-or-minus-1
() `(integer -
1 (,sb
!xc
:array-dimension-limit
)))
49 ;;; A couple of VM-related types that are currently used only on the
50 ;;; alpha platform. -- CSR, 2002-06-24
51 (def!type unsigned-byte-with-a-bite-out
(s bite
)
52 (cond ((eq s
'*) 'integer
)
53 ((and (integerp s
) (> s
0))
54 (let ((bound (ash 1 s
)))
55 `(integer 0 ,(- bound bite
1))))
57 (error "Bad size specified for UNSIGNED-BYTE type specifier: ~S." s
))))
59 ;;; Motivated by the mips port. -- CSR, 2002-08-22
60 (def!type signed-byte-with-a-bite-out
(s bite
)
61 (cond ((eq s
'*) 'integer
)
62 ((and (integerp s
) (> s
1))
63 (let ((bound (ash 1 (1- s
))))
64 `(integer ,(- bound
) ,(- bound bite
1))))
66 (error "Bad size specified for SIGNED-BYTE type specifier: ~S." s
))))
68 (def!type load
/store-index
(scale lowtag min-offset
69 &optional
(max-offset min-offset
))
70 `(integer ,(- (truncate (+ (ash 1 16)
71 (* min-offset sb
!vm
:n-word-bytes
)
74 ,(truncate (- (+ (1- (ash 1 16)) lowtag
)
75 (* max-offset sb
!vm
:n-word-bytes
))
79 (defun displacement-bounds (lowtag element-size data-offset
)
80 (let* ((adjustment (- (* data-offset sb
!vm
:n-word-bytes
) lowtag
))
81 (bytes-per-element (ceiling element-size sb
!vm
:n-byte-bits
))
82 (min (truncate (+ sb
!vm
::minimum-immediate-offset adjustment
)
84 (max (truncate (+ sb
!vm
::maximum-immediate-offset adjustment
)
89 (def!type constant-displacement
(lowtag element-size data-offset
)
90 (flet ((integerify (x)
93 (symbol (symbol-value x
)))))
94 (let ((lowtag (integerify lowtag
))
95 (element-size (integerify element-size
))
96 (data-offset (integerify data-offset
)))
97 (multiple-value-bind (min max
) (displacement-bounds lowtag
100 `(integer ,min
,max
)))))
102 ;;; Similar to FUNCTION, but the result type is "exactly" specified:
103 ;;; if it is an object type, then the function returns exactly one
104 ;;; value, if it is a short form of VALUES, then this short form
105 ;;; specifies the exact number of values.
106 (def!type sfunction
(args &optional result
)
107 (let ((result (cond ((eq result
'*) '*)
109 (not (eq (car result
) 'values
)))
110 `(values ,result
&optional
))
111 ((intersection (cdr result
) sb
!xc
:lambda-list-keywords
)
113 (t `(values ,@(cdr result
) &optional
)))))
114 `(function ,args
,result
)))
118 ;;; FIXME: The SB!KERNEL:INSTANCE here really means CL:CLASS.
119 ;;; However, the CL:CLASS type is only defined once PCL is loaded,
120 ;;; which is before this is evaluated. Once PCL is moved into cold
121 ;;; init, this might be fixable.
122 (def!type type-specifier
() '(or list symbol sb
!kernel
:instance
))
124 ;;; the default value used for initializing character data. The ANSI
125 ;;; spec says this is arbitrary, so we use the value that falls
126 ;;; through when we just let the low-level consing code initialize
127 ;;; all newly-allocated memory to zero.
129 ;;; KLUDGE: It might be nice to use something which is a
130 ;;; STANDARD-CHAR, both to reduce user surprise a little and, probably
131 ;;; more significantly, to help SBCL's cross-compiler (which knows how
132 ;;; to dump STANDARD-CHARs). Unfortunately, the old CMU CL code is
133 ;;; shot through with implicit assumptions that it's #\NULL, and code
134 ;;; in several places (notably both DEFUN MAKE-ARRAY and DEFTRANSFORM
135 ;;; MAKE-ARRAY) would have to be rewritten. -- WHN 2001-10-04
136 (eval-when (:compile-toplevel
:load-toplevel
:execute
)
137 ;; an expression we can use to construct a DEFAULT-INIT-CHAR value
138 ;; at load time (so that we don't need to teach the cross-compiler
139 ;; how to represent and dump non-STANDARD-CHARs like #\NULL)
140 (defparameter *default-init-char-form
* '(code-char 0)))
142 ;;; CHAR-CODE values for ASCII characters which we care about but
143 ;;; which aren't defined in section "2.1.3 Standard Characters" of the
144 ;;; ANSI specification for Lisp
146 ;;; KLUDGE: These are typically used in the idiom (CODE-CHAR
147 ;;; FOO-CHAR-CODE). I suspect that the current implementation is
148 ;;; expanding this idiom into a full call to CODE-CHAR, which is an
149 ;;; annoying overhead. I should check whether this is happening, and
150 ;;; if so, perhaps implement a DEFTRANSFORM or something to stop it.
151 ;;; (or just find a nicer way of expressing characters portably?) --
153 (def!constant bell-char-code
7)
154 (def!constant backspace-char-code
8)
155 (def!constant tab-char-code
9)
156 (def!constant line-feed-char-code
10)
157 (def!constant form-feed-char-code
12)
158 (def!constant return-char-code
13)
159 (def!constant escape-char-code
27)
160 (def!constant rubout-char-code
127)
162 ;;;; type-ish predicates
164 ;;; X may contain cycles -- a conservative approximation. This
165 ;;; occupies a somewhat uncomfortable niche between being fast for
166 ;;; common cases (we don't want to allocate a hash-table), and not
167 ;;; falling down to exponential behaviour for large trees (so we set
168 ;;; an arbitrady depth limit beyond which we punt).
169 (defun maybe-cyclic-p (x &optional
(depth-limit 12))
171 (labels ((safe-cddr (cons)
172 (let ((cdr (cdr cons
)))
175 (check-cycle (object seen depth
)
176 (when (and (consp object
)
177 (or (> depth depth-limit
)
179 (circularp object seen depth
)))
180 (return-from maybe-cyclic-p t
)))
181 (circularp (list seen depth
)
182 ;; Almost regular circular list detection, with a twist:
183 ;; we also check each element of the list for upward
184 ;; references using CHECK-CYCLE.
185 (do ((fast (cons (car list
) (cdr list
)) (safe-cddr fast
))
186 (slow list
(cdr slow
)))
188 ;; Not CDR-circular, need to check remaining CARs yet
189 (do ((tail slow
(and (cdr tail
))))
192 (check-cycle (car tail
) (cons tail seen
) (1+ depth
))))
193 (check-cycle (car slow
) (cons slow seen
) (1+ depth
))
196 (circularp x
(list x
) 0))))
198 ;;; Is X a (possibly-improper) list of at least N elements?
199 (declaim (ftype (function (t index
)) list-of-length-at-least-p
))
200 (defun list-of-length-at-least-p (x n
)
201 (or (zerop n
) ; since anything can be considered an improper list of length 0
203 (list-of-length-at-least-p (cdr x
) (1- n
)))))
205 (declaim (inline singleton-p
))
206 (defun singleton-p (list)
210 ;;; Is X is a positive prime integer?
211 (defun positive-primep (x)
212 ;; This happens to be called only from one place in sbcl-0.7.0, and
213 ;; only for fixnums, we can limit it to fixnums for efficiency. (And
214 ;; if we didn't limit it to fixnums, we should use a cleverer
215 ;; algorithm, since this one scales pretty badly for huge X.)
218 (and (>= x
2) (/= x
4))
220 (not (zerop (rem x
3)))
223 (inc 2 (logxor inc
6)) ;; 2,4,2,4...
225 ((or (= r
0) (> d q
)) (/= r
0))
226 (declare (fixnum inc
))
227 (multiple-value-setq (q r
) (truncate x d
))))))
229 ;;; Could this object contain other objects? (This is important to
230 ;;; the implementation of things like *PRINT-CIRCLE* and the dumper.)
231 (defun compound-object-p (x)
234 (typep x
'(array t
*))))
236 ;;;; the COLLECT macro
238 ;;;; comment from CMU CL: "the ultimate collection macro..."
240 ;;; helper functions for COLLECT, which become the expanders of the
241 ;;; MACROLET definitions created by COLLECT
243 ;;; COLLECT-NORMAL-EXPANDER handles normal collection macros.
245 ;;; COLLECT-LIST-EXPANDER handles the list collection case. N-TAIL
246 ;;; is the pointer to the current tail of the list, or NIL if the list
248 (eval-when (#-sb-xc
:compile-toplevel
:load-toplevel
:execute
)
249 (defun collect-normal-expander (n-value fun forms
)
251 ,@(mapcar (lambda (form) `(setq ,n-value
(,fun
,form
,n-value
))) forms
)
253 (defun collect-list-expander (n-value n-tail forms
)
254 (let ((n-res (gensym)))
256 ,@(mapcar (lambda (form)
257 `(let ((,n-res
(cons ,form nil
)))
259 (setf (cdr ,n-tail
) ,n-res
)
260 (setq ,n-tail
,n-res
))
262 (setq ,n-tail
,n-res
,n-value
,n-res
)))))
266 ;;; Collect some values somehow. Each of the collections specifies a
267 ;;; bunch of things which collected during the evaluation of the body
268 ;;; of the form. The name of the collection is used to define a local
269 ;;; macro, a la MACROLET. Within the body, this macro will evaluate
270 ;;; each of its arguments and collect the result, returning the
271 ;;; current value after the collection is done. The body is evaluated
272 ;;; as a PROGN; to get the final values when you are done, just call
273 ;;; the collection macro with no arguments.
275 ;;; INITIAL-VALUE is the value that the collection starts out with,
276 ;;; which defaults to NIL. FUNCTION is the function which does the
277 ;;; collection. It is a function which will accept two arguments: the
278 ;;; value to be collected and the current collection. The result of
279 ;;; the function is made the new value for the collection. As a
280 ;;; totally magical special-case, FUNCTION may be COLLECT, which tells
281 ;;; us to build a list in forward order; this is the default. If an
282 ;;; INITIAL-VALUE is supplied for COLLECT, the stuff will be RPLACD'd
283 ;;; onto the end. Note that FUNCTION may be anything that can appear
284 ;;; in the functional position, including macros and lambdas.
285 (defmacro collect
(collections &body body
)
288 (dolist (spec collections
)
289 (unless (proper-list-of-length-p spec
1 3)
290 (error "malformed collection specifier: ~S" spec
))
291 (let* ((name (first spec
))
292 (default (second spec
))
293 (kind (or (third spec
) 'collect
))
294 (n-value (gensym (concatenate 'string
297 (push `(,n-value
,default
) binds
)
298 (if (eq kind
'collect
)
299 (let ((n-tail (gensym (concatenate 'string
303 (push `(,n-tail
(last ,n-value
)) binds
)
305 (push `(,name
(&rest args
)
306 (collect-list-expander ',n-value
',n-tail args
))
308 (push `(,name
(&rest args
)
309 (collect-normal-expander ',n-value
',kind args
))
311 `(macrolet ,macros
(let* ,(nreverse binds
) ,@body
))))
313 ;;;; some old-fashioned functions. (They're not just for old-fashioned
314 ;;;; code, they're also used as optimized forms of the corresponding
315 ;;;; general functions when the compiler can prove that they're
318 ;;; like (MEMBER ITEM LIST :TEST #'EQ)
319 (defun memq (item list
)
321 "Return tail of LIST beginning with first element EQ to ITEM."
322 ;; KLUDGE: These could be and probably should be defined as
323 ;; (MEMBER ITEM LIST :TEST #'EQ)),
324 ;; but when I try to cross-compile that, I get an error from
325 ;; LTN-ANALYZE-KNOWN-CALL, "Recursive known function definition". The
326 ;; comments for that error say it "is probably a botched interpreter stub".
327 ;; Rather than try to figure that out, I just rewrote this function from
328 ;; scratch. -- WHN 19990512
329 (do ((i list
(cdr i
)))
331 (when (eq (car i
) item
)
334 ;;; like (ASSOC ITEM ALIST :TEST #'EQ):
335 ;;; Return the first pair of ALIST where ITEM is EQ to the key of
337 (defun assq (item alist
)
338 ;; KLUDGE: CMU CL defined this with
339 ;; (DECLARE (INLINE ASSOC))
340 ;; (ASSOC ITEM ALIST :TEST #'EQ))
341 ;; which is pretty, but which would have required adding awkward
342 ;; build order constraints on SBCL (or figuring out some way to make
343 ;; inline definitions installable at build-the-cross-compiler time,
344 ;; which was too ambitious for now). Rather than mess with that, we
345 ;; just define ASSQ explicitly in terms of more primitive
348 ;; though it may look more natural to write this as
349 ;; (AND PAIR (EQ (CAR PAIR) ITEM))
350 ;; the temptation to do so should be resisted, as pointed out by PFD
351 ;; sbcl-devel 2003-08-16, as NIL elements are rare in association
352 ;; lists. -- CSR, 2003-08-16
353 (when (and (eq (car pair
) item
) (not (null pair
)))
356 ;;; like (DELETE .. :TEST #'EQ):
357 ;;; Delete all LIST entries EQ to ITEM (destructively modifying
358 ;;; LIST), and return the modified LIST.
359 (defun delq (item list
)
361 (do ((x list
(cdr x
))
364 (cond ((eq item
(car x
))
367 (rplacd splice
(cdr x
))))
368 (t (setq splice x
)))))) ; Move splice along to include element.
371 ;;; like (POSITION .. :TEST #'EQ):
372 ;;; Return the position of the first element EQ to ITEM.
373 (defun posq (item list
)
374 (do ((i list
(cdr i
))
377 (when (eq (car i
) item
)
380 (declaim (inline neq
))
384 ;;; not really an old-fashioned function, but what the calling
385 ;;; convention should've been: like NTH, but with the same argument
386 ;;; order as in all the other indexed dereferencing functions, with
387 ;;; the collection first and the index second
388 (declaim (inline nth-but-with-sane-arg-order
))
389 (declaim (ftype (function (list index
) t
) nth-but-with-sane-arg-order
))
390 (defun nth-but-with-sane-arg-order (list index
)
393 (defun adjust-list (list length initial-element
)
394 (let ((old-length (length list
)))
395 (cond ((< old-length length
)
396 (append list
(make-list (- length old-length
)
397 :initial-element initial-element
)))
398 ((> old-length length
)
399 (subseq list
0 length
))
402 ;;;; miscellaneous iteration extensions
404 ;;; like Scheme's named LET
406 ;;; (CMU CL called this ITERATE, and commented it as "the ultimate
407 ;;; iteration macro...". I (WHN) found the old name insufficiently
408 ;;; specific to remind me what the macro means, so I renamed it.)
409 (defmacro named-let
(name binds
&body body
)
411 (unless (proper-list-of-length-p x
2)
412 (error "malformed NAMED-LET variable spec: ~S" x
)))
413 `(labels ((,name
,(mapcar #'first binds
) ,@body
))
414 (,name
,@(mapcar #'second binds
))))
416 (defun filter-dolist-declarations (decls)
417 (mapcar (lambda (decl)
418 `(declare ,@(remove-if
421 (or (eq (car clause
) 'type
)
422 (eq (car clause
) 'ignore
))))
426 ;;; just like DOLIST, but with one-dimensional arrays
427 (defmacro dovector
((elt vector
&optional result
) &body body
)
428 (multiple-value-bind (forms decls
) (parse-body body
:doc-string-allowed nil
)
429 (with-unique-names (index length vec
)
430 `(let ((,vec
,vector
))
431 (declare (type vector
,vec
))
432 (do ((,index
0 (1+ ,index
))
433 (,length
(length ,vec
)))
434 ((>= ,index
,length
) (let ((,elt nil
))
435 ,@(filter-dolist-declarations decls
)
438 (let ((,elt
(aref ,vec
,index
)))
443 ;;; Iterate over the entries in a HASH-TABLE, first obtaining the lock
444 ;;; if the table is a synchronized table.
445 (defmacro dohash
(((key-var value-var
) table
&key result locked
) &body body
)
446 (multiple-value-bind (forms decls
) (parse-body body
:doc-string-allowed nil
)
447 (let* ((gen (gensym))
450 (iter-form `(with-hash-table-iterator (,gen
,n-table
)
452 (multiple-value-bind (,n-more
,key-var
,value-var
) (,gen
)
454 (unless ,n-more
(return ,result
))
456 `(let ((,n-table
,table
))
458 `(with-locked-hash-table (,n-table
)
462 ;;;; hash cache utility
464 (eval-when (:compile-toplevel
:load-toplevel
:execute
)
465 (defvar *profile-hash-cache
* nil
))
467 ;;; a flag for whether it's too early in cold init to use caches so
468 ;;; that we have a better chance of recovering so that we have a
469 ;;; better chance of getting the system running so that we have a
470 ;;; better chance of diagnosing the problem which caused us to use the
473 (defvar *hash-caches-initialized-p
*)
475 ;;; Define a hash cache that associates some number of argument values
476 ;;; with a result value. The TEST-FUNCTION paired with each ARG-NAME
477 ;;; is used to compare the value for that arg in a cache entry with a
478 ;;; supplied arg. The TEST-FUNCTION must not error when passed NIL as
479 ;;; its first arg, but need not return any particular value.
480 ;;; TEST-FUNCTION may be any thing that can be placed in CAR position.
482 ;;; This code used to store all the arguments / return values directly
483 ;;; in the cache vector. This was both interrupt- and thread-unsafe, since
484 ;;; it was possible that *-CACHE-ENTER would scribble over a region of the
485 ;;; cache vector which *-CACHE-LOOKUP had only partially processed. Instead
486 ;;; we now store the contents of each cache bucket as a separate array, which
487 ;;; is stored in the appropriate cell in the cache vector. A new bucket array
488 ;;; is created every time *-CACHE-ENTER is called, and the old ones are never
489 ;;; modified. This means that *-CACHE-LOOKUP will always work with a set
490 ;;; of consistent data. The overhead caused by consing new buckets seems to
491 ;;; be insignificant on the grand scale of things. -- JES, 2006-11-02
493 ;;; NAME is used to define these functions:
494 ;;; <name>-CACHE-LOOKUP Arg*
495 ;;; See whether there is an entry for the specified ARGs in the
496 ;;; cache. If not present, the :DEFAULT keyword (default NIL)
497 ;;; determines the result(s).
498 ;;; <name>-CACHE-ENTER Arg* Value*
499 ;;; Encache the association of the specified args with VALUE.
500 ;;; <name>-CACHE-CLEAR
501 ;;; Reinitialize the cache, invalidating all entries and allowing
502 ;;; the arguments and result values to be GC'd.
504 ;;; These other keywords are defined:
506 ;;; The size of the cache as a power of 2.
507 ;;; :HASH-FUNCTION function
508 ;;; Some thing that can be placed in CAR position which will compute
509 ;;; a value between 0 and (1- (expt 2 <hash-bits>)).
511 ;;; the number of return values cached for each function call
512 ;;; :INIT-WRAPPER <name>
513 ;;; The code for initializing the cache is wrapped in a form with
514 ;;; the specified name. (:INIT-WRAPPER is set to COLD-INIT-FORMS
515 ;;; in type system definitions so that caches will be created
516 ;;; before top level forms run.)
517 (defmacro define-hash-cache
(name args
&key hash-function hash-bits default
518 (init-wrapper 'progn
)
520 (let* ((var-name (symbolicate "*" name
"-CACHE-VECTOR*"))
521 (nargs (length args
))
522 (size (ash 1 hash-bits
))
523 (default-values (if (and (consp default
) (eq (car default
) 'values
))
526 (args-and-values (gensym))
527 (args-and-values-size (+ nargs values
))
531 (unless (= (length default-values
) values
)
532 (error "The number of default values ~S differs from :VALUES ~W."
544 (let ((name (gensym)))
546 (values-refs `(svref ,args-and-values
(+ ,nargs
,i
)))
547 (sets `(setf (svref ,args-and-values
(+ ,nargs
,i
)) ,name
))))
550 (unless (= (length arg
) 2)
551 (error "bad argument spec: ~S" arg
))
552 (let ((arg-name (first arg
))
555 (tests `(,test
(svref ,args-and-values
,n
) ,arg-name
))
556 (sets `(setf (svref ,args-and-values
,n
) ,arg-name
)))
559 (when *profile-hash-cache
*
560 (let ((n-probe (symbolicate "*" name
"-CACHE-PROBES*"))
561 (n-miss (symbolicate "*" name
"-CACHE-MISSES*")))
562 (inits `(setq ,n-probe
0))
563 (inits `(setq ,n-miss
0))
564 (forms `(defvar ,n-probe
))
565 (forms `(defvar ,n-miss
))
566 (forms `(declaim (fixnum ,n-miss
,n-probe
)))))
568 (let ((fun-name (symbolicate name
"-CACHE-LOOKUP")))
571 `(defun ,fun-name
,(arg-vars)
572 ,@(when *profile-hash-cache
*
573 `((incf ,(symbolicate "*" name
"-CACHE-PROBES*"))))
574 (let* ((,n-index
(,hash-function
,@(arg-vars)))
576 (,args-and-values
(svref ,n-cache
,n-index
)))
577 (cond ((and ,args-and-values
579 (values ,@(values-refs)))
581 ,@(when *profile-hash-cache
*
582 `((incf ,(symbolicate "*" name
"-CACHE-MISSES*"))))
585 (let ((fun-name (symbolicate name
"-CACHE-ENTER")))
588 `(defun ,fun-name
(,@(arg-vars) ,@(values-names))
589 (let ((,n-index
(,hash-function
,@(arg-vars)))
591 (,args-and-values
(make-array ,args-and-values-size
)))
593 (setf (svref ,n-cache
,n-index
) ,args-and-values
))
596 (let ((fun-name (symbolicate name
"-CACHE-CLEAR")))
599 (fill ,var-name nil
)))
600 (forms `(,fun-name
)))
602 (inits `(unless (boundp ',var-name
)
603 (setq ,var-name
(make-array ,size
:initial-element nil
))))
604 #!+sb-show
(inits `(setq *hash-caches-initialized-p
* t
))
608 (declaim (type (simple-vector ,size
) ,var-name
))
609 #!-sb-fluid
(declaim (inline ,@(inlines)))
610 (,init-wrapper
,@(inits))
614 ;;; some syntactic sugar for defining a function whose values are
615 ;;; cached by DEFINE-HASH-CACHE
616 (defmacro defun-cached
((name &rest options
&key
(values 1) default
618 args
&body body-decls-doc
)
619 (let ((default-values (if (and (consp default
) (eq (car default
) 'values
))
622 (arg-names (mapcar #'car args
)))
623 (collect ((values-names))
625 (values-names (gensym)))
626 (multiple-value-bind (body decls doc
) (parse-body body-decls-doc
)
628 (define-hash-cache ,name
,args
,@options
)
629 (defun ,name
,arg-names
633 ((not (boundp '*hash-caches-initialized-p
*))
634 ;; This shouldn't happen, but it did happen to me
635 ;; when revising the type system, and it's a lot
636 ;; easier to figure out what what's going on with
637 ;; that kind of problem if the system can be kept
638 ;; alive until cold boot is complete. The recovery
639 ;; mechanism should definitely be conditional on
640 ;; some debugging feature (e.g. SB-SHOW) because
641 ;; it's big, duplicating all the BODY code. -- WHN
642 (/show0
,name
" too early in cold init, uncached")
643 (/show0
,(first arg-names
) "=..")
644 (/hexstr
,(first arg-names
))
647 (multiple-value-bind ,(values-names)
648 (,(symbolicate name
"-CACHE-LOOKUP") ,@arg-names
)
649 (if (and ,@(mapcar (lambda (val def
)
651 (values-names) default-values
))
652 (multiple-value-bind ,(values-names)
654 (,(symbolicate name
"-CACHE-ENTER") ,@arg-names
656 (values ,@(values-names)))
657 (values ,@(values-names))))))))))))
659 (defmacro define-cached-synonym
660 (name &optional
(original (symbolicate "%" name
)))
661 (let ((cached-name (symbolicate "%%" name
"-CACHED")))
663 (defun-cached (,cached-name
:hash-bits
8
664 :hash-function
(lambda (x)
665 (logand (sxhash x
) #xff
)))
667 (apply #',original args
))
668 (defun ,name
(&rest args
)
669 (,cached-name args
)))))
671 ;;; FIXME: maybe not the best place
673 ;;; FIXME: think of a better name -- not only does this not have the
674 ;;; CAR recursion of EQUAL, it also doesn't have the special treatment
675 ;;; of pathnames, bit-vectors and strings.
677 ;;; KLUDGE: This means that we will no longer cache specifiers of the
678 ;;; form '(INTEGER (0) 4). This is probably not a disaster.
680 ;;; A helper function for the type system, which is the main user of
681 ;;; these caches: we must be more conservative than EQUAL for some of
682 ;;; our equality tests, because MEMBER and friends refer to EQLity.
684 (defun equal-but-no-car-recursion (x y
)
689 (eql (car x
) (car y
))
690 (equal-but-no-car-recursion (cdr x
) (cdr y
))))
695 ;;; Note: Almost always you want to use FIND-UNDELETED-PACKAGE-OR-LOSE
696 ;;; instead of this function. (The distinction only actually matters when
697 ;;; PACKAGE-DESIGNATOR is actually a deleted package, and in that case
698 ;;; you generally do want to signal an error instead of proceeding.)
699 (defun %find-package-or-lose
(package-designator)
700 (or (find-package package-designator
)
701 (error 'sb
!kernel
:simple-package-error
702 :package package-designator
703 :format-control
"The name ~S does not designate any package."
704 :format-arguments
(list package-designator
))))
706 ;;; ANSI specifies (in the section for FIND-PACKAGE) that the
707 ;;; consequences of most operations on deleted packages are
708 ;;; unspecified. We try to signal errors in such cases.
709 (defun find-undeleted-package-or-lose (package-designator)
710 (let ((maybe-result (%find-package-or-lose package-designator
)))
711 (if (package-name maybe-result
) ; if not deleted
713 (error 'sb
!kernel
:simple-package-error
714 :package maybe-result
715 :format-control
"The package ~S has been deleted."
716 :format-arguments
(list maybe-result
)))))
718 ;;;; various operations on names
720 ;;; Is NAME a legal function name?
721 (declaim (inline legal-fun-name-p
))
722 (defun legal-fun-name-p (name)
723 (values (valid-function-name-p name
)))
725 (deftype function-name
() '(satisfies legal-fun-name-p
))
727 ;;; Signal an error unless NAME is a legal function name.
728 (defun legal-fun-name-or-type-error (name)
729 (unless (legal-fun-name-p name
)
730 (error 'simple-type-error
732 :expected-type
'function-name
733 :format-control
"invalid function name: ~S"
734 :format-arguments
(list name
))))
736 ;;; Given a function name, return the symbol embedded in it.
738 ;;; The ordinary use for this operator (and the motivation for the
739 ;;; name of this operator) is to convert from a function name to the
740 ;;; name of the BLOCK which encloses its body.
742 ;;; Occasionally the operator is useful elsewhere, where the operator
743 ;;; name is less mnemonic. (Maybe it should be changed?)
744 (declaim (ftype (function ((or symbol cons
)) symbol
) fun-name-block-name
))
745 (defun fun-name-block-name (fun-name)
746 (cond ((symbolp fun-name
)
749 (multiple-value-bind (legalp block-name
)
750 (valid-function-name-p fun-name
)
753 (error "not legal as a function name: ~S" fun-name
))))
755 (error "not legal as a function name: ~S" fun-name
))))
757 (defun looks-like-name-of-special-var-p (x)
759 (let ((name (symbol-name x
)))
760 (and (> (length name
) 2) ; to exclude '* and '**
761 (char= #\
* (aref name
0))
762 (char= #\
* (aref name
(1- (length name
))))))))
764 ;;; This function is to be called just before a change which would affect the
765 ;;; symbol value. We don't absolutely have to call this function before such
766 ;;; changes, since such changes to constants are given as undefined behavior,
767 ;;; it's nice to do so. To circumvent this you need code like this:
770 ;;; (defun set-foo (x) (setq foo x))
771 ;;; (defconstant foo 42)
773 ;;; foo => 13, (constantp 'foo) => t
775 ;;; ...in which case you frankly deserve to lose.
776 (defun about-to-modify-symbol-value (symbol action
&optional
(new-value nil valuep
))
777 (declare (symbol symbol
))
778 (multiple-value-bind (what continue
)
779 (when (eq :constant
(info :variable
:kind symbol
))
781 (values "Veritas aeterna. (can't ~@?)" nil
))
783 (values "Nihil ex nihil. (can't ~@?)" nil
))
785 (values "Can't ~@?." nil
))
787 (values "Constant modification: attempt to ~@?." t
))))
790 (cerror "Modify the constant." what action symbol
)
791 (error what action symbol
)))
793 ;; :VARIABLE :TYPE is in the db only if it is declared, so no need to
795 (let ((type (info :variable
:type symbol
)))
796 (unless (sb!kernel
::%%typep new-value type
)
797 (let ((spec (type-specifier type
)))
798 (error 'simple-type-error
799 :format-control
"Cannot ~@? to ~S (not of type ~S.)"
800 :format-arguments
(list action symbol new-value spec
)
802 :expected-type spec
))))))
805 ;;; If COLD-FSET occurs not at top level, just treat it as an ordinary
806 ;;; assignment instead of doing cold static linking. That way things like
807 ;;; (FLET ((FROB (X) ..))
808 ;;; (DEFUN FOO (X Y) (FROB X) ..)
809 ;;; (DEFUN BAR (Z) (AND (FROB X) ..)))
810 ;;; can still "work" for cold init: they don't do magical static
811 ;;; linking the way that true toplevel DEFUNs do, but at least they do
812 ;;; the linking eventually, so as long as #'FOO and #'BAR aren't
813 ;;; needed until "cold toplevel forms" have executed, it's OK.
814 (defmacro cold-fset
(name lambda
)
816 "~@<COLD-FSET ~S not cross-compiled at top level: demoting to ~
817 (SETF FDEFINITION)~:@>"
819 ;; We convert the LAMBDA expression to the corresponding NAMED-LAMBDA
820 ;; expression so that the compiler can use NAME in debug names etc.
821 (destructuring-bind (lambda-symbol &rest lambda-rest
) lambda
822 (assert (eql lambda-symbol
'lambda
)) ; else dunno how to do conversion
823 `(setf (fdefinition ',name
)
824 (named-lambda ,name
,@lambda-rest
))))
828 ;;;; "The macro ONCE-ONLY has been around for a long time on various
829 ;;;; systems [..] if you can understand how to write and when to use
830 ;;;; ONCE-ONLY, then you truly understand macro." -- Peter Norvig,
831 ;;;; _Paradigms of Artificial Intelligence Programming: Case Studies
832 ;;;; in Common Lisp_, p. 853
834 ;;; ONCE-ONLY is a utility useful in writing source transforms and
835 ;;; macros. It provides a concise way to wrap a LET around some code
836 ;;; to ensure that some forms are only evaluated once.
838 ;;; Create a LET* which evaluates each value expression, binding a
839 ;;; temporary variable to the result, and wrapping the LET* around the
840 ;;; result of the evaluation of BODY. Within the body, each VAR is
841 ;;; bound to the corresponding temporary variable.
842 (defmacro once-only
(specs &body body
)
843 (named-let frob
((specs specs
)
847 (let ((spec (first specs
)))
848 ;; FIXME: should just be DESTRUCTURING-BIND of SPEC
849 (unless (proper-list-of-length-p spec
2)
850 (error "malformed ONCE-ONLY binding spec: ~S" spec
))
851 (let* ((name (first spec
))
852 (exp-temp (gensym "ONCE-ONLY")))
853 `(let ((,exp-temp
,(second spec
))
854 (,name
(gensym ,(symbol-name name
))))
855 `(let ((,,name
,,exp-temp
))
856 ,,(frob (rest specs
) body
))))))))
858 ;;;; various error-checking utilities
860 ;;; This function can be used as the default value for keyword
861 ;;; arguments that must be always be supplied. Since it is known by
862 ;;; the compiler to never return, it will avoid any compile-time type
863 ;;; warnings that would result from a default value inconsistent with
864 ;;; the declared type. When this function is called, it signals an
865 ;;; error indicating that a required &KEY argument was not supplied.
866 ;;; This function is also useful for DEFSTRUCT slot defaults
867 ;;; corresponding to required arguments.
868 (declaim (ftype (function () nil
) missing-arg
))
869 (defun missing-arg ()
871 (/show0
"entering MISSING-ARG")
872 (error "A required &KEY or &OPTIONAL argument was not supplied."))
874 ;;; like CL:ASSERT and CL:CHECK-TYPE, but lighter-weight
876 ;;; (As of sbcl-0.6.11.20, we were using some 400 calls to CL:ASSERT.
877 ;;; The CL:ASSERT restarts and whatnot expand into a significant
878 ;;; amount of code when you multiply them by 400, so replacing them
879 ;;; with this should reduce the size of the system by enough to be
880 ;;; worthwhile. ENFORCE-TYPE is much less common, but might still be
881 ;;; worthwhile, and since I don't really like CERROR stuff deep in the
882 ;;; guts of complex systems anyway, I replaced it too.)
883 (defmacro aver
(expr)
885 (%failed-aver
,(format nil
"~A" expr
))))
887 (defun %failed-aver
(expr-as-string)
888 ;; hackish way to tell we're in a cold sbcl and output the
889 ;; message before signallign error, as it may be this is too
890 ;; early in the cold init.
891 (when (find-package "SB!C")
893 (write-line "failed AVER:")
894 (write-line expr-as-string
)
896 (bug "~@<failed AVER: ~2I~_~S~:>" expr-as-string
))
898 (defun bug (format-control &rest format-arguments
)
900 :format-control format-control
901 :format-arguments format-arguments
))
903 (defmacro enforce-type
(value type
)
904 (once-only ((value value
))
905 `(unless (typep ,value
',type
)
906 (%failed-enforce-type
,value
',type
))))
908 (defun %failed-enforce-type
(value type
)
909 ;; maybe should be TYPE-BUG, subclass of BUG? If it is changed,
910 ;; check uses of it in user-facing code (e.g. WARN)
911 (error 'simple-type-error
914 :format-control
"~@<~S ~_is not a ~_~S~:>"
915 :format-arguments
(list value type
)))
917 ;;; Return a function like FUN, but expecting its (two) arguments in
918 ;;; the opposite order that FUN does.
919 (declaim (inline swapped-args-fun
))
920 (defun swapped-args-fun (fun)
921 (declare (type function fun
))
925 ;;; Return the numeric value of a type bound, i.e. an interval bound
926 ;;; more or less in the format of bounds in ANSI's type specifiers,
927 ;;; where a bare numeric value is a closed bound and a list of a
928 ;;; single numeric value is an open bound.
930 ;;; The "more or less" bit is that the no-bound-at-all case is
931 ;;; represented by NIL (not by * as in ANSI type specifiers); and in
932 ;;; this case we return NIL.
933 (defun type-bound-number (x)
935 (destructuring-bind (result) x result
)
938 ;;; some commonly-occuring CONSTANTLY forms
939 (macrolet ((def-constantly-fun (name constant-expr
)
940 `(setf (symbol-function ',name
)
941 (constantly ,constant-expr
))))
942 (def-constantly-fun constantly-t t
)
943 (def-constantly-fun constantly-nil nil
)
944 (def-constantly-fun constantly-0
0))
946 ;;; If X is a symbol, see whether it is present in *FEATURES*. Also
947 ;;; handle arbitrary combinations of atoms using NOT, AND, OR.
955 (error "too many subexpressions in feature expression: ~S" x
))
957 (error "too few subexpressions in feature expression: ~S" x
))
958 (t (not (featurep (cadr x
))))))
959 ((:and and
) (every #'featurep
(cdr x
)))
960 ((:or or
) (some #'featurep
(cdr x
)))
962 (error "unknown operator in feature expression: ~S." x
))))
963 (symbol (not (null (memq x
*features
*))))))
965 ;;;; utilities for two-VALUES predicates
967 (defmacro not
/type
(x)
968 (let ((val (gensym "VAL"))
969 (win (gensym "WIN")))
970 `(multiple-value-bind (,val
,win
)
973 (values (not ,val
) t
)
976 (defmacro and
/type
(x y
)
977 `(multiple-value-bind (val1 win1
) ,x
978 (if (and (not val1
) win1
)
980 (multiple-value-bind (val2 win2
) ,y
983 (values nil
(and win2
(not val2
))))))))
985 ;;; sort of like ANY and EVERY, except:
986 ;;; * We handle two-VALUES predicate functions, as SUBTYPEP does.
987 ;;; (And if the result is uncertain, then we return (VALUES NIL NIL),
988 ;;; as SUBTYPEP does.)
989 ;;; * THING is just an atom, and we apply OP (an arity-2 function)
990 ;;; successively to THING and each element of LIST.
991 (defun any/type
(op thing list
)
992 (declare (type function op
))
994 (dolist (i list
(values nil certain?
))
995 (multiple-value-bind (sub-value sub-certain?
) (funcall op thing i
)
997 (when sub-value
(return (values t t
)))
998 (setf certain? nil
))))))
999 (defun every/type
(op thing list
)
1000 (declare (type function op
))
1002 (dolist (i list
(if certain?
(values t t
) (values nil nil
)))
1003 (multiple-value-bind (sub-value sub-certain?
) (funcall op thing i
)
1005 (unless sub-value
(return (values nil t
)))
1006 (setf certain? nil
))))))
1010 ;;; These functions are called by the expansion of the DEFPRINTER
1011 ;;; macro to do the actual printing.
1012 (declaim (ftype (function (symbol t stream
) (values))
1013 defprinter-prin1 defprinter-princ
))
1014 (defun defprinter-prin1 (name value stream
)
1015 (defprinter-prinx #'prin1 name value stream
))
1016 (defun defprinter-princ (name value stream
)
1017 (defprinter-prinx #'princ name value stream
))
1018 (defun defprinter-prinx (prinx name value stream
)
1019 (declare (type function prinx
))
1020 (when *print-pretty
*
1021 (pprint-newline :linear stream
))
1022 (format stream
":~A " name
)
1023 (funcall prinx value stream
)
1025 (defun defprinter-print-space (stream)
1026 (write-char #\space stream
))
1028 ;;; Define some kind of reasonable PRINT-OBJECT method for a
1029 ;;; STRUCTURE-OBJECT class.
1031 ;;; NAME is the name of the structure class, and CONC-NAME is the same
1032 ;;; as in DEFSTRUCT.
1034 ;;; The SLOT-DESCS describe how each slot should be printed. Each
1035 ;;; SLOT-DESC can be a slot name, indicating that the slot should
1036 ;;; simply be printed. A SLOT-DESC may also be a list of a slot name
1037 ;;; and other stuff. The other stuff is composed of keywords followed
1038 ;;; by expressions. The expressions are evaluated with the variable
1039 ;;; which is the slot name bound to the value of the slot. These
1040 ;;; keywords are defined:
1042 ;;; :PRIN1 Print the value of the expression instead of the slot value.
1043 ;;; :PRINC Like :PRIN1, only PRINC the value
1044 ;;; :TEST Only print something if the test is true.
1046 ;;; If no printing thing is specified then the slot value is printed
1049 ;;; The structure being printed is bound to STRUCTURE and the stream
1050 ;;; is bound to STREAM.
1051 (defmacro defprinter
((name
1053 (conc-name (concatenate 'simple-string
1060 (reversed-prints nil
)
1061 (stream (gensym "STREAM")))
1062 (flet ((sref (slot-name)
1063 `(,(symbolicate conc-name slot-name
) structure
)))
1064 (dolist (slot-desc slot-descs
)
1066 (setf maybe-print-space nil
1068 (setf maybe-print-space
`(defprinter-print-space ,stream
)))
1069 (cond ((atom slot-desc
)
1070 (push maybe-print-space reversed-prints
)
1071 (push `(defprinter-prin1 ',slot-desc
,(sref slot-desc
) ,stream
)
1074 (let ((sname (first slot-desc
))
1077 (do ((option (rest slot-desc
) (cddr option
)))
1079 (push `(let ((,sname
,(sref sname
)))
1084 ',sname
,sname
,stream
)))))
1086 (case (first option
)
1088 (stuff `(defprinter-prin1
1089 ',sname
,(second option
) ,stream
)))
1091 (stuff `(defprinter-princ
1092 ',sname
,(second option
) ,stream
)))
1093 (:test
(setq test
(second option
)))
1095 (error "bad option: ~S" (first option
)))))))))))
1096 `(def!method print-object
((structure ,name
) ,stream
)
1097 (pprint-logical-block (,stream nil
)
1098 (print-unreadable-object (structure
1101 :identity
,identity
)
1102 ,@(nreverse reversed-prints
))))))
1106 ;;; Given a pathname, return a corresponding physical pathname.
1107 (defun physicalize-pathname (possibly-logical-pathname)
1108 (if (typep possibly-logical-pathname
'logical-pathname
)
1109 (translate-logical-pathname possibly-logical-pathname
)
1110 possibly-logical-pathname
))
1112 (defun deprecation-warning (bad-name &optional good-name
)
1113 (warn "using deprecated ~S~@[, should use ~S instead~]"
1117 ;;; Anaphoric macros
1118 (defmacro awhen
(test &body body
)
1122 (defmacro acond
(&rest clauses
)
1125 (destructuring-bind ((test &body body
) &rest rest
) clauses
1126 (once-only ((test test
))
1128 (let ((it ,test
)) (declare (ignorable it
)),@body
)
1131 ;;; (binding* ({(names initial-value [flag])}*) body)
1132 ;;; FLAG may be NIL or :EXIT-IF-NULL
1134 ;;; This form unites LET*, MULTIPLE-VALUE-BIND and AWHEN.
1135 (defmacro binding
* ((&rest bindings
) &body body
)
1136 (let ((bindings (reverse bindings
)))
1137 (loop with form
= `(progn ,@body
)
1138 for binding in bindings
1139 do
(destructuring-bind (names initial-value
&optional flag
)
1141 (multiple-value-bind (names declarations
)
1144 (let ((name (gensym)))
1145 (values (list name
) `((declare (ignorable ,name
))))))
1147 (values (list names
) nil
))
1149 (collect ((new-names) (ignorable))
1150 (dolist (name names
)
1152 (setq name
(gensym))
1157 `((declare (ignorable ,@(ignorable)))))))))
1158 (setq form
`(multiple-value-bind ,names
1164 `(when ,(first names
) ,form
)))))))
1165 finally
(return form
))))
1167 ;;; Delayed evaluation
1168 (defmacro delay
(form)
1169 `(cons nil
(lambda () ,form
)))
1171 (defun force (promise)
1172 (cond ((not (consp promise
)) promise
)
1173 ((car promise
) (cdr promise
))
1174 (t (setf (car promise
) t
1175 (cdr promise
) (funcall (cdr promise
))))))
1177 (defun promise-ready-p (promise)
1178 (or (not (consp promise
))
1182 (defmacro with-rebound-io-syntax
(&body body
)
1183 `(%with-rebound-io-syntax
(lambda () ,@body
)))
1185 (defun %with-rebound-io-syntax
(function)
1186 (declare (type function function
))
1187 (let ((*package
* *package
*)
1188 (*print-array
* *print-array
*)
1189 (*print-base
* *print-base
*)
1190 (*print-case
* *print-case
*)
1191 (*print-circle
* *print-circle
*)
1192 (*print-escape
* *print-escape
*)
1193 (*print-gensym
* *print-gensym
*)
1194 (*print-length
* *print-length
*)
1195 (*print-level
* *print-level
*)
1196 (*print-lines
* *print-lines
*)
1197 (*print-miser-width
* *print-miser-width
*)
1198 (*print-pretty
* *print-pretty
*)
1199 (*print-radix
* *print-radix
*)
1200 (*print-readably
* *print-readably
*)
1201 (*print-right-margin
* *print-right-margin
*)
1202 (*read-base
* *read-base
*)
1203 (*read-default-float-format
* *read-default-float-format
*)
1204 (*read-eval
* *read-eval
*)
1205 (*read-suppress
* *read-suppress
*)
1206 (*readtable
* *readtable
*))
1207 (funcall function
)))
1209 ;;; Bind a few "potentially dangerous" printer control variables to
1210 ;;; safe values, respecting current values if possible.
1211 (defmacro with-sane-io-syntax
(&body forms
)
1212 `(call-with-sane-io-syntax (lambda () ,@forms
)))
1214 (defun call-with-sane-io-syntax (function)
1215 (declare (type function function
))
1216 (macrolet ((true (sym)
1217 `(and (boundp ',sym
) ,sym
)))
1218 (let ((*print-readably
* nil
)
1219 (*print-level
* (or (true *print-level
*) 6))
1220 (*print-length
* (or (true *print-length
*) 12)))
1221 (funcall function
))))
1223 ;;; Returns a list of members of LIST. Useful for dealing with circular lists.
1224 ;;; For a dotted list returns a secondary value of T -- in which case the
1225 ;;; primary return value does not include the dotted tail.
1226 (defun list-members (list)
1228 (do ((tail (cdr list
) (cdr tail
))
1229 (members (list (car list
)) (cons (car tail
) members
)))
1230 ((or (not (consp tail
)) (eq tail list
))
1231 (values members
(not (listp tail
)))))))
1233 ;;; Default evaluator mode (interpeter / compiler)
1235 (declaim (type (member :compile
#!+sb-eval
:interpret
) *evaluator-mode
*))
1236 (defparameter *evaluator-mode
* :compile
1238 "Toggle between different evaluator implementations. If set to :COMPILE,
1239 an implementation of EVAL that calls the compiler will be used. If set
1240 to :INTERPRET, an interpreter will be used.")
1242 ;;; Helper for making the DX closure allocation in macros expanding
1243 ;;; to CALL-WITH-FOO less ugly.
1244 (defmacro dx-flet
(functions &body forms
)
1246 (declare (#+sb-xc-host dynamic-extent
#-sb-xc-host truly-dynamic-extent
1247 ,@(mapcar (lambda (func) `(function ,(car func
))) functions
)))
1250 ;;; Another similar one.
1251 (defmacro dx-let
(bindings &body forms
)
1253 (declare (#+sb-xc-host dynamic-extent
#-sb-xc-host truly-dynamic-extent
1254 ,@(mapcar (lambda (bind) (if (consp bind
) (car bind
) bind
))
1258 (in-package "SB!KERNEL")
1260 (defun fp-zero-p (x)
1262 (single-float (zerop x
))
1263 (double-float (zerop x
))
1265 (long-float (zerop x
))
1268 (defun neg-fp-zero (x)
1272 (make-unportable-float :single-float-negative-zero
)
1276 (make-unportable-float :double-float-negative-zero
)
1281 (make-unportable-float :long-float-negative-zero
)