2c6456dde35f3d322c0f86e020891913102dc101
[sbcl.git] / tests / type.impure.lisp
1 ;;;; This software is part of the SBCL system. See the README file for
2 ;;;; more information.
3 ;;;;
4 ;;;; While most of SBCL is derived from the CMU CL system, the test
5 ;;;; files (like this one) were written from scratch after the fork
6 ;;;; from CMU CL.
7 ;;;; 
8 ;;;; This software is in the public domain and is provided with
9 ;;;; absolutely no warranty. See the COPYING and CREDITS files for
10 ;;;; more information.
11
12 (load "assertoid.lisp")
13 (use-package "ASSERTOID")
14
15 (defmacro assert-nil-nil (expr)
16   `(assert (equal '(nil nil) (multiple-value-list ,expr))))
17 (defmacro assert-nil-t (expr)
18   `(assert (equal '(nil t) (multiple-value-list ,expr))))
19 (defmacro assert-t-t (expr)
20   `(assert (equal '(t t) (multiple-value-list ,expr))))
21
22 (defmacro assert-t-t-or-uncertain (expr)
23   `(assert (let ((list (multiple-value-list ,expr)))
24              (or (equal '(nil nil) list)
25                  (equal '(t t) list)))))
26
27 (let ((types '(character
28                integer fixnum (integer 0 10)
29                single-float (single-float -1.0 1.0) (single-float 0.1)
30                (real 4 8) (real -1 7) (real 2 11)
31                null symbol keyword
32                (member #\a #\b #\c) (member 1 #\a) (member 3.0 3.3)
33                (integer -1 1)
34                unsigned-byte
35                (rational -1 7) (rational -2 4)
36                ratio
37                )))
38   (dolist (i types)
39     (format t "type I=~S~%" i)
40     (dolist (j types)
41       (format t "  type J=~S~%" j)
42       (assert (subtypep i `(or ,i ,j)))
43       (assert (subtypep i `(or ,j ,i)))
44       (assert (subtypep i `(or ,i ,i ,j)))
45       (assert (subtypep i `(or ,j ,i)))
46       (dolist (k types)
47         (format t "    type K=~S~%" k)
48         (assert (subtypep `(or ,i ,j) `(or ,i ,j ,k)))
49         (assert (subtypep `(or ,i ,j) `(or ,k ,j ,i)))))))
50
51 ;;; gotchas that can come up in handling subtypeness as "X is a
52 ;;; subtype of Y if each of the elements of X is a subtype of Y"
53 (let ((subtypep-values (multiple-value-list
54                         (subtypep '(single-float -1.0 1.0)
55                                   '(or (real -100.0 0.0)
56                                        (single-float 0.0 100.0))))))
57   (assert (member subtypep-values
58                   '(;; The system isn't expected to
59                     ;; understand the subtype relationship.
60                     (nil nil)
61                     ;; But if it does, that'd be neat.
62                     (t t)
63                     ;; (And any other return would be wrong.)
64                     )
65                   :test #'equal)))
66
67 (defun type-evidently-= (x y)
68   (and (subtypep x y)
69        (subtypep y x)))
70
71 (assert (subtypep 'single-float 'float))
72
73 (assert (type-evidently-= '(integer 0 10) '(or (integer 0 5) (integer 4 10))))
74
75 ;;; Bug 50(c,d): numeric types with empty ranges should be NIL
76 (assert (type-evidently-= 'nil '(integer (0) (0))))
77 (assert (type-evidently-= 'nil '(rational (0) (0))))
78 (assert (type-evidently-= 'nil '(float (0.0) (0.0))))
79
80 ;;; sbcl-0.6.10 did (UPGRADED-ARRAY-ELEMENT-TYPE 'SOME-UNDEF-TYPE)=>T
81 ;;; and (UPGRADED-COMPLEX-PART-TYPE 'SOME-UNDEF-TYPE)=>T.
82 (assert (raises-error? (upgraded-array-element-type 'some-undef-type)))
83 (assert (eql (upgraded-array-element-type t) t))
84 (assert (raises-error? (upgraded-complex-part-type 'some-undef-type)))
85 (assert (subtypep (upgraded-complex-part-type 'fixnum) 'real))
86
87 ;;; Do reasonable things with undefined types, and with compound types
88 ;;; built from undefined types.
89 ;;;
90 ;;; part I: TYPEP
91 (assert (typep #(11) '(simple-array t 1)))
92 (assert (typep #(11) '(simple-array (or integer symbol) 1)))
93 (assert (raises-error? (typep #(11) '(simple-array undef-type 1))))
94 (assert (not (typep 11 '(simple-array undef-type 1))))
95 ;;; part II: SUBTYPEP
96
97 (assert (subtypep '(vector some-undef-type) 'vector))
98 (assert (not (subtypep '(vector some-undef-type) 'integer)))
99 (assert-nil-nil (subtypep 'utype-1 'utype-2))
100 (assert-nil-nil (subtypep '(vector utype-1) '(vector utype-2)))
101 (assert-nil-nil (subtypep '(vector utype-1) '(vector t)))
102 (assert-nil-nil (subtypep '(vector t) '(vector utype-2)))
103
104 ;;; ANSI specifically disallows bare AND and OR symbols as type specs.
105 #| ; Alas, this is part of bug 10, still unfixed as of sbcl-0.7.2.
106 (assert (raises-error? (typep 11 'and)))
107 (assert (raises-error? (typep 11 'or)))
108 |#
109 ;;; Of course empty lists of subtypes are still OK.
110 (assert (typep 11 '(and)))
111 (assert (not (typep 11 '(or))))
112
113 ;;; bug 12: type system didn't grok nontrivial intersections
114 (assert (subtypep '(and symbol (satisfies keywordp)) 'symbol))
115 (assert (not (subtypep '(and symbol (satisfies keywordp)) 'null)))
116 (assert (subtypep 'keyword 'symbol))
117 (assert (not (subtypep 'symbol 'keyword)))
118 (assert (subtypep 'ratio 'real))
119 (assert (subtypep 'ratio 'number))
120
121 ;;; bug 50.g: Smarten up hairy type specifiers slightly. We may wish
122 ;;; to revisit this, perhaps by implementing a COMPLEMENT type
123 ;;; (analogous to UNION and INTERSECTION) to take the logic out of the
124 ;;; HAIRY domain.
125 (assert-nil-t (subtypep 'atom 'cons))
126 (assert-nil-t (subtypep 'cons 'atom))
127 ;;; These two are desireable but not necessary for ANSI conformance;
128 ;;; maintenance work on other parts of the system broke them in
129 ;;; sbcl-0.7.13.11 -- CSR
130 #+nil
131 (assert-nil-t (subtypep '(not list) 'cons))
132 #+nil
133 (assert-nil-t (subtypep '(not float) 'single-float))
134 (assert-t-t (subtypep '(not atom) 'cons))
135 (assert-t-t (subtypep 'cons '(not atom)))
136 ;;; ANSI requires that SUBTYPEP relationships among built-in primitive
137 ;;; types never be uncertain, i.e. never return NIL as second value.
138 ;;; Prior to about sbcl-0.7.2.6, ATOM caused a lot of problems here
139 ;;; (because it's a negation type, implemented as a HAIRY-TYPE, and
140 ;;; CMU CL's HAIRY-TYPE logic punted a lot).
141 (assert-t-t (subtypep 'integer 'atom))
142 (assert-t-t (subtypep 'function 'atom))
143 (assert-nil-t (subtypep 'list 'atom))
144 (assert-nil-t (subtypep 'atom 'integer))
145 (assert-nil-t (subtypep 'atom 'function))
146 (assert-nil-t (subtypep 'atom 'list))
147 ;;; ATOM is equivalent to (NOT CONS):
148 (assert-t-t (subtypep 'integer '(not cons)))
149 (assert-nil-t (subtypep 'list '(not cons)))
150 (assert-nil-t (subtypep '(not cons) 'integer))
151 (assert-nil-t (subtypep '(not cons) 'list))
152 ;;; And we'd better check that all the named types are right. (We also
153 ;;; do some more tests on ATOM here, since once CSR experimented with
154 ;;; making it a named type.)
155 (assert-t-t (subtypep 'nil 'nil))
156 (assert-t-t (subtypep 'nil 'atom))
157 (assert-t-t (subtypep 'nil 't))
158 (assert-nil-t (subtypep 'atom 'nil))
159 (assert-t-t (subtypep 'atom 'atom))
160 (assert-t-t (subtypep 'atom 't))
161 (assert-nil-t (subtypep 't 'nil))
162 (assert-nil-t (subtypep 't 'atom))
163 (assert-t-t (subtypep 't 't))
164 ;;; Also, LIST is now somewhat special, in that (NOT LIST) should be
165 ;;; recognized as a subtype of ATOM:
166 (assert-t-t (subtypep '(not list) 'atom))
167 (assert-nil-t (subtypep 'atom '(not list)))
168 ;;; These used to fail, because when the two arguments to subtypep are
169 ;;; of different specifier-type types (e.g. HAIRY and UNION), there
170 ;;; are two applicable type methods -- in this case
171 ;;; HAIRY-COMPLEX-SUBTYPEP-ARG1-TYPE-METHOD and
172 ;;; UNION-COMPLEX-SUBTYPEP-ARG2-TYPE-METHOD. Both of these exist, but
173 ;;; [!%]INVOKE-TYPE-METHOD aren't smart enough to know that if one of
174 ;;; them returns NIL, NIL (indicating uncertainty) it should try the
175 ;;; other. However, as of sbcl-0.7.2.6 or so, CALL-NEXT-METHOD-ish
176 ;;; logic in those type methods fixed it.
177 (assert-nil-t (subtypep '(not cons) 'list))
178 (assert-nil-t (subtypep '(not single-float) 'float))
179 ;;; Somewhere along the line (probably when adding CALL-NEXT-METHOD-ish
180 ;;; logic in SUBTYPEP type methods) we fixed bug 58 too:
181 (assert-t-t (subtypep '(and zilch integer) 'zilch))
182 (assert-t-t (subtypep '(and integer zilch) 'zilch))
183
184 ;;; Bug 84: SB-KERNEL:CSUBTYPEP was a bit enthusiastic at
185 ;;; special-casing calls to subtypep involving *EMPTY-TYPE*,
186 ;;; corresponding to the NIL type-specifier; we were bogusly returning
187 ;;; NIL, T (indicating surety) for the following:
188 (assert-nil-nil (subtypep '(satisfies some-undefined-fun) 'nil))
189
190 ;;; It turns out that, as of sbcl-0.7.2, we require to be able to
191 ;;; detect this to compile src/compiler/node.lisp (and in particular,
192 ;;; the definition of the component structure). Since it's a sensible
193 ;;; thing to want anyway, let's test for it here:
194 (assert-t-t (subtypep '(or some-undefined-type (member :no-ir2-yet :dead))
195                       '(or some-undefined-type (member :no-ir2-yet :dead))))
196 ;;; BUG 158 (failure to compile loops with vector references and
197 ;;; increments of greater than 1) was a symptom of type system
198 ;;; uncertainty, to wit:
199 (assert-t-t (subtypep '(and (mod 536870911) (or (integer 0 0) (integer 2 536870912)))
200                       '(mod 536870911))) ; aka SB-INT:INDEX.
201 \f
202 ;;;; Douglas Thomas Crosher rewrote the CMU CL type test system to
203 ;;;; allow inline type tests for CONDITIONs and STANDARD-OBJECTs, and
204 ;;;; generally be nicer, and Martin Atzmueller ported the patches.
205 ;;;; They look nice but they're nontrivial enough that it's not
206 ;;;; obvious from inspection that everything is OK. Let's make sure
207 ;;;; that things still basically work.
208
209 ;; structure type tests setup
210 (defstruct structure-foo1)
211 (defstruct (structure-foo2 (:include structure-foo1))
212   x)
213 (defstruct (structure-foo3 (:include structure-foo2)))
214 (defstruct (structure-foo4 (:include structure-foo3))
215   y z)
216
217 ;; structure-class tests setup
218 (defclass structure-class-foo1 () () (:metaclass cl:structure-class))
219 (defclass structure-class-foo2 (structure-class-foo1)
220   () (:metaclass cl:structure-class))
221 (defclass structure-class-foo3 (structure-class-foo2)
222   () (:metaclass cl:structure-class))
223 (defclass structure-class-foo4 (structure-class-foo3)
224   () (:metaclass cl:structure-class))
225
226 ;; standard-class tests setup
227 (defclass standard-class-foo1 () () (:metaclass cl:standard-class))
228 (defclass standard-class-foo2 (standard-class-foo1)
229   () (:metaclass cl:standard-class))
230 (defclass standard-class-foo3 (standard-class-foo2)
231   () (:metaclass cl:standard-class))
232 (defclass standard-class-foo4 (standard-class-foo3)
233   () (:metaclass cl:standard-class))
234
235 ;; condition tests setup
236 (define-condition condition-foo1 (condition) ())
237 (define-condition condition-foo2 (condition-foo1) ())
238 (define-condition condition-foo3 (condition-foo2) ())
239 (define-condition condition-foo4 (condition-foo3) ())
240
241 ;;; inline type tests
242 (format t "~&/setting up *TESTS-OF-INLINE-TYPE-TESTS*~%")
243 (defparameter *tests-of-inline-type-tests*
244   '(progn
245
246      ;; structure type tests
247      (assert (typep (make-structure-foo3) 'structure-foo2))
248      (assert (not (typep (make-structure-foo1) 'structure-foo4)))
249      (assert (typep (nth-value 1
250                                (ignore-errors (structure-foo2-x
251                                                (make-structure-foo1))))
252                     'type-error))
253      (assert (null (ignore-errors
254                      (setf (structure-foo2-x (make-structure-foo1)) 11))))
255
256      ;; structure-class tests
257      (assert (typep (make-instance 'structure-class-foo3)
258                     'structure-class-foo2))
259      (assert (not (typep (make-instance 'structure-class-foo1)
260                          'structure-class-foo4)))
261      (assert (null (ignore-errors
262                      (setf (slot-value (make-instance 'structure-class-foo1)
263                                        'x)
264                            11))))
265
266      ;; standard-class tests
267      (assert (typep (make-instance 'standard-class-foo3)
268                     'standard-class-foo2))
269      (assert (not (typep (make-instance 'standard-class-foo1)
270                          'standard-class-foo4)))
271      (assert (null (ignore-errors
272                      (setf (slot-value (make-instance 'standard-class-foo1) 'x)
273                            11))))
274
275      ;; condition tests
276      (assert (typep (make-condition 'condition-foo3)
277                     'condition-foo2))
278      (assert (not (typep (make-condition 'condition-foo1)
279                          'condition-foo4)))
280      (assert (null (ignore-errors
281                      (setf (slot-value (make-condition 'condition-foo1) 'x)
282                            11))))
283      (assert (subtypep 'error 't))
284      (assert (subtypep 'simple-condition 'condition))
285      (assert (subtypep 'simple-error 'simple-condition))
286      (assert (subtypep 'simple-error 'error))
287      (assert (not (subtypep 'condition 'simple-condition)))
288      (assert (not (subtypep 'error 'simple-error)))
289      (assert (eq (car (sb-pcl:class-direct-superclasses
290                        (find-class 'simple-condition)))
291                  (find-class 'condition)))
292
293     (let ((subclasses (mapcar #'find-class
294                               '(simple-type-error
295                                 simple-error
296                                 simple-warning
297                                 sb-int:simple-file-error
298                                 sb-int:simple-style-warning))))
299       (assert (null (set-difference
300                      (sb-pcl:class-direct-subclasses (find-class
301                                                       'simple-condition))
302                      subclasses))))
303
304      ;; precedence lists
305      (assert (equal (sb-pcl:class-precedence-list
306                      (find-class 'simple-condition))
307                     (mapcar #'find-class '(simple-condition
308                                            condition
309                                            sb-kernel:instance
310                                            t))))
311
312      ;; stream classes
313      (assert (equal (sb-pcl:class-direct-superclasses (find-class
314                                                        'fundamental-stream))
315                     (mapcar #'find-class '(standard-object stream))))
316      (assert (null (set-difference
317                     (sb-pcl:class-direct-subclasses (find-class
318                                                      'fundamental-stream))
319                     (mapcar #'find-class '(fundamental-binary-stream
320                                            fundamental-character-stream
321                                            fundamental-output-stream
322                                            fundamental-input-stream)))))
323      (assert (equal (sb-pcl:class-precedence-list (find-class
324                                                    'fundamental-stream))
325                     (mapcar #'find-class '(fundamental-stream
326                                            standard-object
327                                            sb-pcl::std-object
328                                            sb-pcl::slot-object
329                                            stream
330                                            sb-kernel:instance
331                                            t))))
332      (assert (equal (sb-pcl:class-precedence-list (find-class
333                                                    'fundamental-stream))
334                     (mapcar #'find-class '(fundamental-stream
335                                            standard-object
336                                            sb-pcl::std-object
337                                            sb-pcl::slot-object stream
338                                            sb-kernel:instance t))))
339      (assert (subtypep (find-class 'stream) (find-class t)))
340      (assert (subtypep (find-class 'fundamental-stream) 'stream))
341      (assert (not (subtypep 'stream 'fundamental-stream)))))
342 ;;; Test under the interpreter.
343 (eval *tests-of-inline-type-tests*)
344 (format t "~&/done with interpreted *TESTS-OF-INLINE-TYPE-TESTS*~%")
345 ;;; Test under the compiler.
346 (defun tests-of-inline-type-tests ()
347   #.*tests-of-inline-type-tests*)
348 (tests-of-inline-type-tests)
349 (format t "~&/done with compiled (TESTS-OF-INLINE-TYPE-TESTS)~%")
350 \f
351 ;;; Redefinition of classes should alter the type hierarchy (BUG 140):
352 (defclass superclass () ())
353 (defclass maybe-subclass () ())
354 (assert-nil-t (subtypep 'maybe-subclass 'superclass))
355 (defclass maybe-subclass (superclass) ())
356 (assert-t-t (subtypep 'maybe-subclass 'superclass))
357 (defclass maybe-subclass () ())
358 (assert-nil-t (subtypep 'maybe-subclass 'superclass))
359 \f
360 ;;; Prior to sbcl-0.7.6.27, there was some confusion in ARRAY types
361 ;;; specialized on some as-yet-undefined type which would cause this
362 ;;; program to fail (bugs #123 and #165). Verify that it doesn't.
363 (defun foo (x)
364   (declare (type (vector bar) x))
365   (aref x 1))
366 (deftype bar () 'single-float)
367 (assert (eql (foo (make-array 3 :element-type 'bar :initial-element 0.0f0))
368              0.0f0))
369 \f
370 ;;; success
371 (quit :unix-status 104)