1.0.42.1: add release script
[sbcl.git] / tests / ctor.impure.lisp
blob12c1f896b0b1384db798a0b692df0082d115aa18
1 ;;;; gray-box testing of the constructor optimization machinery
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; While most of SBCL is derived from the CMU CL system, the test
7 ;;;; files (like this one) were written from scratch after the fork
8 ;;;; from CMU CL.
9 ;;;;
10 ;;;; This software is in the public domain and is provided with
11 ;;;; absolutely no warranty. See the COPYING and CREDITS files for
12 ;;;; more information.
14 (load "test-util.lisp")
15 (load "compiler-test-util.lisp")
17 (defpackage "CTOR-TEST"
18 (:use "CL" "TEST-UTIL" "COMPILER-TEST-UTIL"))
20 (in-package "CTOR-TEST")
22 (defclass no-slots () ())
24 (defun make-no-slots ()
25 (make-instance 'no-slots))
26 (compile 'make-no-slots)
28 (defmethod update-instance-for-redefined-class
29 ((object no-slots) added discarded plist &rest initargs)
30 (declare (ignore initargs))
31 (error "Called U-I-F-R-C on ~A" object))
33 (assert (typep (make-no-slots) 'no-slots))
35 (make-instances-obsolete 'no-slots)
37 (assert (typep (make-no-slots) 'no-slots))
38 (assert (typep (funcall #'(sb-pcl::ctor no-slots nil)) 'no-slots))
40 (defclass one-slot ()
41 ((a :initarg :a)))
43 (defun make-one-slot-a (a)
44 (make-instance 'one-slot :a a))
45 (compile 'make-one-slot-a)
46 (defun make-one-slot-noa ()
47 (make-instance 'one-slot))
48 (compile 'make-one-slot-noa)
50 (defmethod update-instance-for-redefined-class
51 ((object one-slot) added discarded plist &rest initargs)
52 (declare (ignore initargs))
53 (error "Called U-I-F-R-C on ~A" object))
55 (assert (= (slot-value (make-one-slot-a 3) 'a) 3))
56 (assert (not (slot-boundp (make-one-slot-noa) 'a)))
58 (make-instances-obsolete 'one-slot)
60 (assert (= (slot-value (make-one-slot-a 3) 'a) 3))
61 (assert (= (slot-value (funcall #'(sb-pcl::ctor one-slot nil :a sb-pcl::\.p0.) 4) 'a) 4))
62 (assert (not (slot-boundp (make-one-slot-noa) 'a)))
63 (assert (not (slot-boundp (funcall #'(sb-pcl::ctor one-slot nil)) 'a)))
65 (defclass one-slot-superclass ()
66 ((b :initarg :b)))
67 (defclass one-slot-subclass (one-slot-superclass)
68 ())
70 (defun make-one-slot-subclass (b)
71 (make-instance 'one-slot-subclass :b b))
72 (compile 'make-one-slot-subclass)
74 (defmethod update-instance-for-redefined-class
75 ((object one-slot-superclass) added discarded plist &rest initargs)
76 (declare (ignore initargs))
77 (error "Called U-I-F-R-C on ~A" object))
79 (assert (= (slot-value (make-one-slot-subclass 2) 'b) 2))
81 (make-instances-obsolete 'one-slot-subclass)
83 (assert (= (slot-value (make-one-slot-subclass 2) 'b) 2))
84 (assert (= (slot-value (funcall #'(sb-pcl::ctor one-slot-subclass nil :b sb-pcl::\.p0.) 3) 'b) 3))
85 (make-instances-obsolete 'one-slot-superclass)
87 (assert (= (slot-value (make-one-slot-subclass 2) 'b) 2))
88 (assert (= (slot-value (funcall #'(sb-pcl::ctor one-slot-subclass nil :b sb-pcl::\.p0.) 4) 'b) 4))
90 ;;; Tests for CTOR optimization of non-constant class args and constant class object args
91 (defun find-ctor-caches (fun)
92 (remove-if-not (lambda (value)
93 (and (consp value) (eq 'sb-pcl::ctor-cache (car value))))
94 (find-value-cell-values fun)))
96 (let* ((cmacro (compiler-macro-function 'make-instance))
97 (opt 0)
98 (wrapper (lambda (form env)
99 (let ((res (funcall cmacro form env)))
100 (unless (eq form res)
101 (incf opt))
102 res))))
103 (sb-ext:without-package-locks
104 (unwind-protect
105 (progn
106 (setf (compiler-macro-function 'make-instance) wrapper)
107 (with-test (:name (make-instance :non-constant-class))
108 (assert (= 0 opt))
109 (let ((f (compile nil `(lambda (class)
110 (make-instance class :b t)))))
111 (assert (= 1 (length (find-ctor-caches f))))
112 (assert (= 1 opt))
113 (assert (typep (funcall f 'one-slot-subclass) 'one-slot-subclass))))
114 (with-test (:name (make-instance :constant-class-object))
115 (let ((f (compile nil `(lambda ()
116 (make-instance ,(find-class 'one-slot-subclass) :b t)))))
117 (assert (not (find-ctor-caches f)))
118 (assert (= 2 opt))
119 (assert (typep (funcall f) 'one-slot-subclass))))
120 (with-test (:name (make-instance :constant-non-std-class-object))
121 (let ((f (compile nil `(lambda ()
122 (make-instance ,(find-class 'structure-object))))))
123 (assert (not (find-ctor-caches f)))
124 (assert (= 3 opt))
125 (assert (typep (funcall f) 'structure-object))))
126 (with-test (:name (make-instance :constant-non-std-class-name))
127 (let ((f (compile nil `(lambda ()
128 (make-instance 'structure-object)))))
129 (assert (not (find-ctor-caches f)))
130 (assert (= 4 opt))
131 (assert (typep (funcall f) 'structure-object)))))
132 (setf (compiler-macro-function 'make-instance) cmacro))))
134 (with-test (:name (make-instance :ctor-inline-cache-resize))
135 (let* ((f (compile nil `(lambda (name) (make-instance name))))
136 (classes (loop repeat (* 2 sb-pcl::+ctor-table-max-size+)
137 collect (class-name (eval `(defclass ,(gentemp) () ())))))
138 (count 0)
139 (caches (find-ctor-caches f))
140 (cache (pop caches)))
141 (assert cache)
142 (assert (not caches))
143 (assert (not (cdr cache)))
144 (dolist (class classes)
145 (assert (typep (funcall f (if (oddp count) class (find-class class))) class))
146 (incf count)
147 (cond ((<= count sb-pcl::+ctor-list-max-size+)
148 (unless (consp (cdr cache))
149 (error "oops, wanted list cache, got: ~S" cache))
150 (unless (= count (length (cdr cache)))
151 (error "oops, wanted ~S elts in cache, got: ~S" count cache)))
153 (assert (simple-vector-p (cdr cache))))))
154 (dolist (class classes)
155 (assert (typep (funcall f (if (oddp count) class (find-class class))) class))
156 (incf count))))
158 ;;; Make sure we get default initargs right with on the FAST-MAKE-INSTANCE path CTORs
159 (defclass some-class ()
160 ((aroundp :initform nil :reader aroundp))
161 (:default-initargs :x :success1))
163 (defmethod initialize-instance :around ((some-class some-class) &key (x :fail?))
164 (unless (eq x :success1)
165 (error "Default initarg lossage"))
166 (setf (slot-value some-class 'aroundp) t)
167 (when (next-method-p)
168 (call-next-method)))
170 (with-test (:name (make-instance :ctor-default-initargs-1))
171 (assert (aroundp (eval `(make-instance 'some-class))))
172 (let ((fun (compile nil `(lambda () (make-instance 'some-class)))))
173 (assert (aroundp (funcall fun)))
174 ;; make sure we tested what we think we tested...
175 (let ((ctors (find-named-callees fun :type 'sb-pcl::ctor)))
176 (assert ctors)
177 (assert (not (cdr ctors)))
178 (assert (find-named-callees (car ctors) :name 'sb-pcl::fast-make-instance)))))
180 ;;; Make sure we get default initargs right with on the FAST-MAKE-INSTANCE path CTORs
181 ;;; in more interesting cases as well...
182 (defparameter *some-counter* 0)
183 (let* ((x 'success2))
184 (defclass some-class2 ()
185 ((aroundp :initform nil :reader aroundp))
186 (:default-initargs :x (progn (incf *some-counter*) x))))
188 (defmethod initialize-instance :around ((some-class some-class2) &key (x :fail2?))
189 (unless (eq x 'success2)
190 (error "Default initarg lossage"))
191 (setf (slot-value some-class 'aroundp) t)
192 (when (next-method-p)
193 (call-next-method)))
195 (with-test (:name (make-instance :ctor-default-initargs-2))
196 (assert (= 0 *some-counter*))
197 (assert (aroundp (eval `(make-instance 'some-class2))))
198 (assert (= 1 *some-counter*))
199 (let ((fun (compile nil `(lambda () (make-instance 'some-class2)))))
200 (assert (= 1 *some-counter*))
201 (assert (aroundp (funcall fun)))
202 (assert (= 2 *some-counter*))
203 ;; make sure we tested what we think we tested...
204 (let ((ctors (find-named-callees fun :type 'sb-pcl::ctor)))
205 (assert ctors)
206 (assert (not (cdr ctors)))
207 (assert (find-named-callees (car ctors) :name 'sb-pcl::fast-make-instance)))))
209 ;;; No compiler notes, please
210 (locally (declare (optimize safety))
211 (defclass type-check-thing ()
212 ((slot :type (integer 0) :initarg :slot))))
213 (with-test (:name (make-instance :no-compile-note-at-runtime))
214 (let ((fun (compile nil `(lambda (x)
215 (declare (optimize safety))
216 (make-instance 'type-check-thing :slot x)))))
217 (handler-bind ((sb-ext:compiler-note #'error))
218 (funcall fun 41)
219 (funcall fun 13))))
221 ;;; NO-APPLICABLE-METHOD called
222 (defmethod no-applicable-method ((gf (eql #'make-instance)) &rest args)
223 (cons :no-applicable-method args))
224 (with-test (:name :constant-invalid-class-arg)
225 (assert (equal
226 '(:no-applicable-method "FOO" :quux 14)
227 (funcall (compile nil `(lambda (x) (make-instance "FOO" :quux x))) 14)))
228 (assert (equal
229 '(:no-applicable-method 'abc zot 1 bar 2)
230 (funcall (compile nil `(lambda (x y) (make-instance ''abc 'zot x 'bar y)))
231 1 2))))
232 (with-test (:name :variable-invalid-class-arg)
233 (assert (equal
234 '(:no-applicable-method "FOO" :quux 14)
235 (funcall (compile nil `(lambda (c x) (make-instance c :quux x))) "FOO" 14)))
236 (assert (equal
237 '(:no-applicable-method 'abc zot 1 bar 2)
238 (funcall (compile nil `(lambda (c x y) (make-instance c 'zot x 'bar y)))
239 ''abc 1 2))))
241 ;;;; success