Remove single use function, revise comment, fix inlining failure
[sbcl.git] / src / code / pred.lisp
blob43a5948e3d0688d589648053644ecc80436b0235
1 ;;;; predicate functions (EQUAL and friends, and type predicates)
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")
14 ;;;; miscellaneous non-primitive predicates
16 #!-sb-fluid (declaim (inline streamp))
17 (defun streamp (stream)
18 (typep stream 'stream))
20 ;;; various (VECTOR FOO) type predicates, not implemented as simple
21 ;;; widetag tests
22 (macrolet
23 ((def ()
24 `(progn
25 ,@(loop for (name spec) in *vector-without-complex-typecode-infos*
26 collect `(defun ,name (x)
27 (or (typep x '(simple-array ,spec (*)))
28 (and (complex-vector-p x)
29 (do ((data (%array-data x) (%array-data data)))
30 ((not (array-header-p data)) (typep data '(simple-array ,spec (*))))))))))))
31 (def))
33 ;;; Is X an extended sequence?
34 ;; This is like the "hierarchical layout depths for other things"
35 ;; case of the TYPEP transform (cf 'typetran'). Ideally it would
36 ;; be preferable to share TYPEP's code rather than repeat it here.
37 (declaim (maybe-inline extended-sequence-p))
38 (defun extended-sequence-p (x)
39 (let* ((slayout #.(info :type :compiler-layout 'sequence))
40 (depthoid #.(layout-depthoid (info :type :compiler-layout 'sequence)))
41 (layout
42 ;; It is not an error to define a class that is both SEQUENCE and
43 ;; FUNCALLABLE-INSTANCE with metaclass FUNCALLABLE-STANDARD-CLASS
44 (cond ((%instancep x) (%instance-layout x))
45 ((funcallable-instance-p x) (%funcallable-instance-layout x))
46 (t (return-from extended-sequence-p nil)))))
47 (when (layout-invalid layout)
48 (setq layout (update-object-layout-or-invalid x slayout)))
49 ;; It's _nearly_ impossible to create an instance which is exactly
50 ;; of type SEQUENCE. To wit: (make-instance 'sequence) =>
51 ;; "Cannot allocate an instance of #<BUILT-IN-CLASS SEQUENCE>."
52 ;; We should not need to check for that, just the 'inherits' vector.
53 ;; However, bootstrap code does a sleazy thing, making an instance of
54 ;; the abstract base type which is impossible for user code to do.
55 ;; Preferably the prototype instance for SEQUENCE would be one that could
56 ;; exist, so it would be a STANDARD-OBJECT and SEQUENCE. But it's not.
57 ;; Hence we have to check for a layout that no code using the documented
58 ;; sequence API would ever see, just to get the boundary case right.
59 ;; Note also:
60 ;; - Some builtins use a prototype object that is strictly deeper than
61 ;; layout of the named class because it is indeed the case that no
62 ;; object's layout can ever be EQ to that of the ancestor.
63 ;; e.g. a fixnum as representative of class REAL
64 ;; - Some builtins actually fail (TYPEP (CLASS-PROTOTYPE X) X)
65 ;; but that's not an excuse for getting SEQUENCE wrong:
66 ;; (CLASS-PROTOTYPE (FIND-CLASS 'FLOAT)) => 42
67 ;; (CLASS-PROTOTYPE (FIND-CLASS 'VECTOR)) => 42
68 ;; (CLASS-PROTOTYPE (FIND-CLASS 'LIST)) => 42
69 ;; (CLASS-PROTOTYPE (FIND-CLASS 'STRING)) => 42
70 (let ((inherits (layout-inherits (truly-the layout layout))))
71 (declare (optimize (safety 0)))
72 (eq (if (> (length inherits) depthoid) (svref inherits depthoid) layout)
73 slayout))))
75 ;;; Is X a SEQUENCE? Harder than just (OR VECTOR LIST)
76 (defun sequencep (x)
77 (declare (inline extended-sequence-p))
78 (or (listp x) (vectorp x) (extended-sequence-p x)))
80 ;;;; primitive predicates. These must be supported directly by the
81 ;;;; compiler.
83 (defun not (object)
84 "Return T if X is NIL, otherwise return NIL."
85 (not object))
87 ;;; All the primitive type predicate wrappers share a parallel form..
88 (macrolet ((def-type-predicate-wrapper (pred)
89 (let* ((name (symbol-name pred))
90 (stem (string-left-trim "%" (string-right-trim "P-" name)))
91 (article (if (position (schar name 0) "AEIOU") "an" "a")))
92 `(defun ,pred (object)
93 ,(format nil
94 "Return true if OBJECT is ~A ~A, and NIL otherwise."
95 article
96 stem)
97 ;; (falling through to low-level implementation)
98 (,pred object)))))
99 (def-type-predicate-wrapper array-header-p)
100 (def-type-predicate-wrapper arrayp)
101 (def-type-predicate-wrapper atom)
102 ;; Testing for BASE-CHAR-P is usually redundant on #-sb-unicode,
103 ;; remove it there completely so that #-sb-unicode build will
104 ;; break when it's used.
105 #!+sb-unicode (def-type-predicate-wrapper base-char-p)
106 (def-type-predicate-wrapper base-string-p)
107 #!+sb-unicode (def-type-predicate-wrapper character-string-p)
108 (def-type-predicate-wrapper bignump)
109 (def-type-predicate-wrapper bit-vector-p)
110 (def-type-predicate-wrapper characterp)
111 (def-type-predicate-wrapper code-component-p)
112 (def-type-predicate-wrapper consp)
113 (def-type-predicate-wrapper compiled-function-p)
114 (def-type-predicate-wrapper complexp)
115 (def-type-predicate-wrapper complex-double-float-p)
116 (def-type-predicate-wrapper complex-float-p)
117 #!+long-float (def-type-predicate-wrapper complex-long-float-p)
118 (def-type-predicate-wrapper complex-rational-p)
119 (def-type-predicate-wrapper complex-single-float-p)
120 ;; (COMPLEX-VECTOR-P is not included here since it's awkward to express
121 ;; the type it tests for in the Common Lisp type system, and since it's
122 ;; only used in the implementation of a few specialized things.)
123 (def-type-predicate-wrapper double-float-p)
124 (def-type-predicate-wrapper extended-char-p)
125 (def-type-predicate-wrapper fdefn-p)
126 (def-type-predicate-wrapper fixnump)
127 (def-type-predicate-wrapper floatp)
128 (def-type-predicate-wrapper functionp)
129 (def-type-predicate-wrapper integerp)
130 (def-type-predicate-wrapper listp)
131 (def-type-predicate-wrapper long-float-p)
132 #!-(or x86 x86-64) (def-type-predicate-wrapper lra-p)
133 (def-type-predicate-wrapper null)
134 (def-type-predicate-wrapper numberp)
135 (def-type-predicate-wrapper rationalp)
136 (def-type-predicate-wrapper ratiop)
137 (def-type-predicate-wrapper realp)
138 (def-type-predicate-wrapper short-float-p)
139 (def-type-predicate-wrapper single-float-p)
140 #!+sb-simd-pack (def-type-predicate-wrapper simd-pack-p)
141 (def-type-predicate-wrapper %instancep)
142 (def-type-predicate-wrapper symbolp)
143 (def-type-predicate-wrapper %other-pointer-p)
144 (def-type-predicate-wrapper system-area-pointer-p)
145 (def-type-predicate-wrapper unbound-marker-p)
146 (def-type-predicate-wrapper weak-pointer-p)
147 #!-64-bit
148 (progn
149 (def-type-predicate-wrapper unsigned-byte-32-p)
150 (def-type-predicate-wrapper signed-byte-32-p))
151 #!+64-bit
152 (progn
153 (def-type-predicate-wrapper unsigned-byte-64-p)
154 (def-type-predicate-wrapper signed-byte-64-p))
155 ;; Specialized array types
156 (macrolet ((saetp-defs ()
157 `(progn
158 ,@(map 'list
159 (lambda (saetp)
160 `(def-type-predicate-wrapper
161 ,(symbolicate (sb!vm:saetp-primitive-type-name saetp) "-P")))
162 sb!vm:*specialized-array-element-type-properties*))))
163 (saetp-defs))
164 ;; Other array types
165 (def-type-predicate-wrapper simple-array-p)
166 (def-type-predicate-wrapper simple-rank-1-array-*-p)
167 (def-type-predicate-wrapper simple-string-p)
168 (def-type-predicate-wrapper stringp)
169 (def-type-predicate-wrapper vectorp)
170 (def-type-predicate-wrapper vector-nil-p))
172 #!+(or x86 x86-64 arm arm64)
173 (defun fixnum-mod-p (x limit)
174 (and (fixnump x)
175 (<= 0 x limit)))
177 #!+(or x86 x86-64 ppc)
178 (defun %other-pointer-subtype-p (x choices)
179 (and (%other-pointer-p x)
180 (member (%other-pointer-widetag x) choices)
183 ;;; Return the layout for an object. This is the basic operation for
184 ;;; finding out the "type" of an object, and is used for generic
185 ;;; function dispatch. The standard doesn't seem to say as much as it
186 ;;; should about what this returns for built-in objects. For example,
187 ;;; it seems that we must return NULL rather than LIST when X is NIL
188 ;;; so that GF's can specialize on NULL.
189 (declaim (inline layout-of))
190 #-sb-xc-host
191 (defun layout-of (x)
192 (declare (optimize (speed 3) (safety 0)))
193 #!+(and compact-instance-header x86-64)
194 (values (%primitive layout-of x
195 (load-time-value sb!kernel::**built-in-class-codes** t)))
196 #!-(and compact-instance-header x86-64)
197 (cond ((%instancep x) (%instance-layout x))
198 ((funcallable-instance-p x) (%funcallable-instance-layout x))
199 ;; Compiler can dump literal layouts, which handily sidesteps
200 ;; the question of when cold-init runs L-T-V forms.
201 ((null x) #.(find-layout 'null))
203 ;; Note that WIDETAG-OF is slightly suboptimal here and could be
204 ;; improved - we've already ruled out some of the lowtags.
205 (svref (load-time-value sb!kernel::**built-in-class-codes** t)
206 (widetag-of x)))))
208 (declaim (inline classoid-of))
209 #-sb-xc-host
210 (defun classoid-of (object)
211 "Return the class of the supplied object, which may be any Lisp object, not
212 just a CLOS STANDARD-OBJECT."
213 (layout-classoid (layout-of object)))
215 ;;; Return the specifier for the type of object. This is not simply
216 ;;; (TYPE-SPECIFIER (CTYPE-OF OBJECT)) because CTYPE-OF has different
217 ;;; goals than TYPE-OF. In particular, speed is more important than
218 ;;; precision here, and it is not permitted to return member types,
219 ;;; negation, union, or intersection types.
220 (defun type-of (object)
221 "Return the type of OBJECT."
222 (declare (explicit-check))
223 ;; We have special logic for everything except arrays.
224 ;; Arrays use CTYPE-OF and then convert the answer to a specifier.
225 (typecase object
226 (fixnum
227 (cond
228 ((<= 0 object 1) 'bit)
229 ((< object 0) 'fixnum)
230 (t '(integer 0 #.sb!xc:most-positive-fixnum))))
231 (integer
232 (if (>= object 0)
233 '(integer #.(1+ sb!xc:most-positive-fixnum))
234 'bignum))
235 (character
236 (typecase object
237 (standard-char 'standard-char)
238 (base-char 'base-char)
239 (extended-char 'extended-char)))
240 ;; We "have to" (or have chosen to) pick off KEYWORD and BOOLEAN,
241 ;; so we may as well have a branch that returns early for any SYMBOL
242 ;; rather than falling into the CLASSOID-based test. But then since we
243 ;; do that, we also have to pick off NIL so that it doesn't say SYMBOL.
244 (symbol
245 (cond ((eq object t) 'boolean)
246 ((eq object nil) 'null)
247 ((eq (symbol-package object) *keyword-package*) 'keyword)
248 (t 'symbol)))
249 ((or array complex #!+sb-simd-pack simd-pack)
250 (let ((sb!kernel::*unparse-allow-negation* nil))
251 (declare (special sb!kernel::*unparse-allow-negation*)) ; forward ref
252 (type-specifier (ctype-of object))))
254 (let* ((classoid (classoid-of object))
255 (name (classoid-name classoid)))
256 (if (%instancep object)
257 (case name
258 (sb!alien-internals:alien-value
259 `(alien
260 ,(sb!alien-internals:unparse-alien-type
261 (sb!alien-internals:alien-value-type object))))
263 (let ((pname (classoid-proper-name classoid)))
264 (if (classoid-p pname)
265 (classoid-pcl-class pname)
266 pname))))
267 name)))))
269 ;;;; equality predicates
271 ;;; This is real simple, 'cause the compiler takes care of it.
272 (defun eq (obj1 obj2)
273 "Return T if OBJ1 and OBJ2 are the same object, otherwise NIL."
274 (eq obj1 obj2))
275 ;;; and this too, but it's only needed for backends on which
276 ;;; IR1 might potentially transform EQL into %EQL/INTEGER.
277 #!+integer-eql-vop
278 (defun %eql/integer (obj1 obj2)
279 ;; This is just for constant folding, no need to transform into the %EQL/INTEGER VOP
280 (eql obj1 obj2))
282 (declaim (inline %eql))
283 (defun %eql (obj1 obj2)
284 "Return T if OBJ1 and OBJ2 represent the same object, otherwise NIL."
285 (or (eq obj1 obj2)
286 (if (or (typep obj2 'fixnum)
287 (not (typep obj2 'number)))
289 ;; I would think that we could do slightly better here by testing that
290 ;; both objs are OTHER-POINTER-P with equal %OTHER-POINTER-WIDETAGs.
291 ;; Then dispatch on obj2 and elide the TYPEP on obj1 using TRULY-THE.
292 ;; Also would need to deal with immediate single-float for 64-bit.
293 (macrolet ((foo (&rest stuff)
294 `(typecase obj2
295 ,@(mapcar (lambda (foo)
296 (let ((type (car foo))
297 (fn (cadr foo)))
298 `(,type
299 (and (typep obj1 ',type)
300 (,fn obj1 obj2)))))
301 stuff))))
302 (foo
303 (single-float eql)
304 (double-float eql)
305 #!+long-float
306 (long-float eql)
307 (bignum
308 #!-integer-eql-vop (lambda (x y) (zerop (bignum-compare x y)))
309 #!+integer-eql-vop eql) ; will become %eql/integer
310 (ratio
311 (lambda (x y)
312 (and (eql (numerator x) (numerator y))
313 (eql (denominator x) (denominator y)))))
314 ((complex single-float)
315 (lambda (x y)
316 (and (eql (realpart x) (realpart y))
317 (eql (imagpart x) (imagpart y)))))
318 ((complex double-float)
319 (lambda (x y)
320 (and (eql (realpart x) (realpart y))
321 (eql (imagpart x) (imagpart y)))))
322 ((complex rational)
323 (lambda (x y)
324 (and (eql (realpart x) (realpart y))
325 (eql (imagpart x) (imagpart y))))))))))
327 (defun eql (x y)
328 (%eql x y))
330 (defun bit-vector-= (x y)
331 (declare (type bit-vector x y))
332 (cond ((eq x y))
333 ((and (simple-bit-vector-p x)
334 (simple-bit-vector-p y))
335 (bit-vector-= x y)) ; DEFTRANSFORM
337 (and (= (length x) (length y))
338 (with-array-data ((x x) (start-x) (end-x) :force-inline t
339 :check-fill-pointer t)
340 (with-array-data ((y y) (start-y) (end-y) :force-inline t
341 :check-fill-pointer t)
342 (declare (ignore end-y))
343 (loop for x-i fixnum from start-x below end-x
344 for y-i fixnum from start-y
345 always (or (= (sbit x x-i)
346 (sbit y y-i))))))))))
348 (defun equal (x y)
349 "Return T if X and Y are EQL or if they are structured components whose
350 elements are EQUAL. Strings and bit-vectors are EQUAL if they are the same
351 length and have identical components. Other arrays must be EQ to be EQUAL."
352 ;; Non-tail self-recursion implemented with a local auxiliary function
353 ;; is a lot faster than doing it the straightforward way (at least
354 ;; on x86oids) due to calling convention differences. -- JES, 2005-12-30
355 (labels ((equal-aux (x y)
356 (cond ((%eql x y)
358 ((consp x)
359 (and (consp y)
360 (equal-aux (car x) (car y))
361 (equal-aux (cdr x) (cdr y))))
362 ((stringp x)
363 (and (stringp y) (string= x y)))
364 ((pathnamep x)
365 (and (pathnamep y) (pathname= x y)))
366 ((bit-vector-p x)
367 (and (bit-vector-p y)
368 (bit-vector-= x y)))
369 (t nil))))
370 ;; Use MAYBE-INLINE to get the inline expansion only once (instead
371 ;; of 200 times with INLINE). -- JES, 2005-12-30
372 (declare (maybe-inline equal-aux))
373 (equal-aux x y)))
375 ;;; Like EQUAL, but any two gensyms whose names are STRING= are equalish.
376 (defun fun-names-equalish (x y)
377 (named-let recurse ((x x) (y y))
378 (cond ((eql x y) t) ; not performance-critical: don't inline %EQL here
379 ((consp x) (and (consp y)
380 (recurse (car x) (car y))
381 (recurse (cdr x) (cdr y))))
382 ((and (symbolp x) (not (symbol-package x)))
383 (and (symbolp y) (not (symbol-package y)) (string= x y)))
385 (equal x y)))))
387 ;;; EQUALP comparison of HASH-TABLE values
388 (defun hash-table-equalp (x y)
389 (declare (type hash-table x y))
390 (or (eq x y)
391 (and (hash-table-p y)
392 (eql (hash-table-count x) (hash-table-count y))
393 (eql (hash-table-test x) (hash-table-test y))
394 (block comparison-of-entries
395 (maphash (lambda (key x-value)
396 (multiple-value-bind (y-value y-value-p)
397 (gethash key y)
398 (unless (and y-value-p (equalp x-value y-value))
399 (return-from comparison-of-entries nil))))
401 t))))
403 (defun instance-equalp (x y)
404 (let ((layout-x (%instance-layout x)))
405 (and
406 (eq layout-x (%instance-layout y))
407 (logtest +structure-layout-flag+ (layout-%flags layout-x))
408 (macrolet ((slot-ref-equalp ()
409 `(let ((x-el (%instance-ref x i))
410 (y-el (%instance-ref y i)))
411 (or (eq x-el y-el) (equalp x-el y-el)))))
412 (if (eql (layout-bitmap layout-x) sb!kernel::+layout-all-tagged+)
413 (loop for i of-type index from sb!vm:instance-data-start
414 below (layout-length layout-x)
415 always (slot-ref-equalp))
416 (let ((comparators (layout-equalp-tests layout-x)))
417 (unless (= (length comparators)
418 (- (layout-length layout-x) sb!vm:instance-data-start))
419 (bug "EQUALP got incomplete instance layout"))
420 ;; See remark at the source code for %TARGET-DEFSTRUCT
421 ;; explaining how to use the vector of comparators.
422 (loop for i of-type index from sb!vm:instance-data-start
423 below (layout-length layout-x)
424 for test = (data-vector-ref
425 comparators (- i sb!vm:instance-data-start))
426 always (cond ((eql test 0) (slot-ref-equalp))
427 ((functionp test)
428 (funcall test i x y))
429 (t)))))))))
431 ;;; Doesn't work on simple vectors
432 (defun array-equal-p (x y)
433 (declare (array x y))
434 (let ((rank (array-rank x)))
435 (and
436 (= rank (array-rank y))
437 (dotimes (axis rank t)
438 (unless (= (%array-dimension x axis)
439 (%array-dimension y axis))
440 (return nil)))
441 (with-array-data ((x x) (start-x) (end-x) :force-inline t
442 :array-header-p t)
443 (with-array-data ((y y) (start-y) (end-y) :force-inline t
444 :array-header-p t)
445 (declare (ignore end-y))
446 (let* ((reffers %%data-vector-reffers%%)
447 (getter-x (truly-the function (svref reffers (%other-pointer-widetag x))))
448 (getter-y (truly-the function (svref reffers (%other-pointer-widetag y)))))
449 (loop for x-i fixnum from start-x below end-x
450 for y-i fixnum from start-y
451 for x-el = (funcall getter-x x x-i)
452 for y-el = (funcall getter-y y y-i)
453 always (or (eq x-el y-el)
454 (equalp x-el y-el)))))))))
456 (defun vector-equalp (x y)
457 (declare (vector x y))
458 (let ((length (length x)))
459 (and (= length (length y))
460 (with-array-data ((x x) (start-x) (end-x) :force-inline t
461 :check-fill-pointer t)
462 (with-array-data ((y y) (start-y) (end-y) :force-inline t
463 :check-fill-pointer t)
464 (declare (ignore end-y))
465 (let* ((reffers %%data-vector-reffers%%)
466 (getter-x (truly-the function (svref reffers (%other-pointer-widetag x))))
467 (getter-y (truly-the function (svref reffers (%other-pointer-widetag y)))))
468 (loop for x-i fixnum from start-x below end-x
469 for y-i fixnum from start-y
470 for x-el = (funcall getter-x x x-i)
471 for y-el = (funcall getter-y y y-i)
472 always (or (eq x-el y-el)
473 (equalp x-el y-el)))))))))
475 (defun equalp (x y)
476 #+nil ; KLUDGE: If doc string, should be accurate: Talk about structures
477 ; and HASH-TABLEs.
478 "This is like EQUAL, except more liberal in several respects.
479 Numbers may be of different types, as long as the values are identical
480 after coercion. Characters may differ in alphabetic case. Vectors and
481 arrays must have identical dimensions and EQUALP elements, but may differ
482 in their type restriction."
483 (cond ((eq x y) t)
484 ((characterp x) (and (characterp y) (char-equal x y)))
485 ((numberp x) (and (numberp y) (= x y)))
486 ((consp x)
487 (and (consp y)
488 (equalp (car x) (car y))
489 (equalp (cdr x) (cdr y))))
490 ((pathnamep x)
491 (and (pathnamep y) (pathname= x y)))
492 ((hash-table-p x)
493 (and (hash-table-p y)
494 (hash-table-equalp x y)))
495 ((%instancep x)
496 (and (%instancep y)
497 (instance-equalp x y)))
498 ((and (bit-vector-p x)
499 (bit-vector-p y))
500 (bit-vector-= x y))
501 ((vectorp x)
502 (and (vectorp y)
503 (vector-equalp x y)))
504 ((arrayp x)
505 (and (arrayp y)
506 (array-equal-p x y)))
507 (t nil)))
509 (/show0 "about to do test cases in pred.lisp")
510 (let ((test-cases `((0.0 ,(load-time-value (make-unportable-float :single-float-negative-zero)) t)
511 (0.0 1.0 nil)
512 (#c(1 0) #c(1.0 0.0) t)
513 (#c(0 1) #c(0.0 1.0) t)
514 (#c(1.1 0.0) #c(11/10 0) nil) ; due to roundoff error
515 ("Hello" "hello" t)
516 ("Hello" #(#\h #\E #\l #\l #\o) t)
517 ("Hello" "goodbye" nil))))
518 (/show0 "TEST-CASES bound in pred.lisp")
519 (dolist (test-case test-cases)
520 (/show0 "about to do a TEST-CASE in pred.lisp")
521 (destructuring-bind (x y expected-result) test-case
522 (let* ((result (equalp x y))
523 (bresult (if result 1 0))
524 (expected-bresult (if expected-result 1 0)))
525 (unless (= bresult expected-bresult)
526 (/show0 "failing test in pred.lisp")
527 (error "failed test (EQUALP ~S ~S)" x y))))))
528 (/show0 "done with test cases in pred.lisp")