1.0.37.31: Use (WITH-TEST ...) consistently in threads.impure.lisp.
[sbcl.git] / tests / threads.impure.lisp
1 ;;;; miscellaneous tests of thread stuff
2
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 ;;;; absoluely no warranty. See the COPYING and CREDITS files for
12 ;;;; more information.
13
14 ; WHITE-BOX TESTS
15
16 (in-package "SB-THREAD")
17 (use-package :test-util)
18 (use-package "ASSERTOID")
19
20 (setf sb-unix::*on-dangerous-select* :error)
21
22 (defun wait-for-threads (threads)
23   (mapc (lambda (thread) (sb-thread:join-thread thread :default nil)) threads)
24   (assert (not (some #'sb-thread:thread-alive-p threads))))
25
26 (with-test (:name (:threads :trivia))
27   (assert (eql 1 (length (list-all-threads))))
28
29   (assert (eq *current-thread*
30               (find (thread-name *current-thread*) (list-all-threads)
31                     :key #'thread-name :test #'equal)))
32
33   (assert (thread-alive-p *current-thread*)))
34
35 (with-test (:name (:with-mutex :basics))
36   (let ((mutex (make-mutex)))
37     (with-mutex (mutex)
38       mutex)))
39
40 (with-test (:name (:with-spinlock :basics))
41   (let ((spinlock (make-spinlock)))
42     (with-spinlock (spinlock))))
43
44 (sb-alien:define-alien-routine "check_deferrables_blocked_or_lose"
45     void
46   (where sb-alien:unsigned-long))
47 (sb-alien:define-alien-routine "check_deferrables_unblocked_or_lose"
48     void
49   (where sb-alien:unsigned-long))
50
51 (with-test (:name (:interrupt-thread :basics :no-unwinding))
52   (let ((a 0))
53     (interrupt-thread *current-thread* (lambda () (setq a 1)))
54     (assert (eql a 1))))
55
56 (with-test (:name (:interrupt-thread :deferrables-blocked))
57   (sb-thread:interrupt-thread sb-thread:*current-thread*
58                               (lambda ()
59                                 (check-deferrables-blocked-or-lose 0))))
60
61 (with-test (:name (:interrupt-thread :deferrables-unblocked))
62   (sb-thread:interrupt-thread sb-thread:*current-thread*
63                               (lambda ()
64                                 (with-interrupts
65                                   (check-deferrables-unblocked-or-lose 0)))))
66
67 (with-test (:name (:interrupt-thread :nlx))
68   (catch 'xxx
69     (sb-thread:interrupt-thread sb-thread:*current-thread*
70                                 (lambda ()
71                                   (check-deferrables-blocked-or-lose 0)
72                                   (throw 'xxx nil))))
73   (check-deferrables-unblocked-or-lose 0))
74
75 #-sb-thread (sb-ext:quit :unix-status 104)
76
77 ;;;; Now the real tests...
78
79 (with-test (:name (:interrupt-thread :deferrables-unblocked-by-spinlock))
80   (let ((spinlock (sb-thread::make-spinlock))
81         (thread (sb-thread:make-thread (lambda ()
82                                          (loop (sleep 1))))))
83     (sb-thread::get-spinlock spinlock)
84     (sb-thread:interrupt-thread thread
85                                 (lambda ()
86                                   (check-deferrables-blocked-or-lose 0)
87                                   (sb-thread::get-spinlock spinlock)
88                                   (check-deferrables-unblocked-or-lose 0)
89                                   (sb-ext:quit)))
90     (sleep 1)
91     (sb-thread::release-spinlock spinlock)))
92
93 ;;; compare-and-swap
94
95 (defmacro defincf (name accessor &rest args)
96   `(defun ,name (x)
97      (let* ((old (,accessor x ,@args))
98          (new (1+ old)))
99     (loop until (eq old (sb-ext:compare-and-swap (,accessor x ,@args) old new))
100        do (setf old (,accessor x ,@args)
101                 new (1+ old)))
102     new)))
103
104 (defstruct cas-struct (slot 0))
105
106 (defincf incf-car car)
107 (defincf incf-cdr cdr)
108 (defincf incf-slot cas-struct-slot)
109 (defincf incf-symbol-value symbol-value)
110 (defincf incf-svref/1 svref 1)
111 (defincf incf-svref/0 svref 0)
112
113 (defmacro def-test-cas (name init incf op)
114   `(with-test (:name ,name)
115      (flet ((,name (n)
116               (declare (fixnum n))
117               (let* ((x ,init)
118                      (run nil)
119                      (threads
120                       (loop repeat 10
121                             collect (sb-thread:make-thread
122                                      (lambda ()
123                                        (loop until run
124                                              do (sb-thread:thread-yield))
125                                        (loop repeat n do (,incf x)))))))
126                 (setf run t)
127                 (dolist (th threads)
128                   (sb-thread:join-thread th))
129                 (assert (= (,op x) (* 10 n))))))       
130        (,name 200000))))
131
132 (def-test-cas test-cas-car (cons 0 nil) incf-car car)
133 (def-test-cas test-cas-cdr (cons nil 0) incf-cdr cdr)
134 (def-test-cas test-cas-slot (make-cas-struct) incf-slot cas-struct-slot)
135 (def-test-cas test-cas-value (let ((x '.x.))
136                                (set x 0)
137                                x)
138   incf-symbol-value symbol-value)
139 (def-test-cas test-cas-svref/0 (vector 0 nil) incf-svref/0 (lambda (x)
140                                                              (svref x 0)))
141 (def-test-cas test-cas-svref/1 (vector nil 0) incf-svref/1 (lambda (x)
142                                                              (svref x 1)))
143 (format t "~&compare-and-swap tests done~%")
144
145 (with-test (:name (:threads :more-trivia)))
146 (let ((old-threads (list-all-threads))
147       (thread (make-thread (lambda ()
148                              (assert (find *current-thread* *all-threads*))
149                              (sleep 2))))
150       (new-threads (list-all-threads)))
151   (assert (thread-alive-p thread))
152   (assert (eq thread (first new-threads)))
153   (assert (= (1+ (length old-threads)) (length new-threads)))
154   (sleep 3)
155   (assert (not (thread-alive-p thread))))
156
157 (with-test (:name '(:join-thread :nlx :default))
158   (let ((sym (gensym)))
159     (assert (eq sym (join-thread (make-thread (lambda () (sb-ext:quit)))
160                                  :default sym)))))
161
162 (with-test (:name '(:join-thread :nlx :error))
163   (raises-error? (join-thread (make-thread (lambda () (sb-ext:quit))))
164                  join-thread-error))
165
166 (with-test (:name '(:join-thread :multiple-values))
167   (assert (equal '(1 2 3)
168                  (multiple-value-list
169                   (join-thread (make-thread (lambda () (values 1 2 3))))))))
170
171 ;;; We had appalling scaling properties for a while.  Make sure they
172 ;;; don't reappear.
173 (defun scaling-test (function &optional (nthreads 5))
174   "Execute FUNCTION with NTHREADS lurking to slow it down."
175   (let ((queue (sb-thread:make-waitqueue))
176         (mutex (sb-thread:make-mutex)))
177     ;; Start NTHREADS idle threads.
178     (dotimes (i nthreads)
179       (sb-thread:make-thread (lambda ()
180                                (with-mutex (mutex)
181                                  (sb-thread:condition-wait queue mutex))
182                                (sb-ext:quit))))
183     (let ((start-time (get-internal-run-time)))
184       (funcall function)
185       (prog1 (- (get-internal-run-time) start-time)
186         (sb-thread:condition-broadcast queue)))))
187 (defun fact (n)
188   "A function that does work with the CPU."
189   (if (zerop n) 1 (* n (fact (1- n)))))
190 (let ((work (lambda () (fact 15000))))
191   (let ((zero (scaling-test work 0))
192         (four (scaling-test work 4)))
193     ;; a slightly weak assertion, but good enough for starters.
194     (assert (< four (* 1.5 zero)))))
195
196 ;;; For one of the interupt-thread tests, we want a foreign function
197 ;;; that does not make syscalls
198
199 (with-open-file (o "threads-foreign.c" :direction :output :if-exists :supersede)
200   (format o "void loop_forever() { while(1) ; }~%"))
201 (sb-ext:run-program
202  #-sunos "cc" #+sunos "gcc"
203  (or #+(or linux freebsd sunos) '(#+x86-64 "-fPIC"
204                                   "-shared" "-o" "threads-foreign.so" "threads-foreign.c")
205      #+darwin '(#+x86-64 "-arch" #+x86-64 "x86_64"
206                 "-dynamiclib" "-o" "threads-foreign.so" "threads-foreign.c")
207      (error "Missing shared library compilation options for this platform"))
208  :search t)
209 (sb-alien:load-shared-object (truename "threads-foreign.so"))
210 (sb-alien:define-alien-routine loop-forever sb-alien:void)
211 (delete-file "threads-foreign.c")
212
213
214 ;;; elementary "can we get a lock and release it again"
215 (with-test (:name (:mutex :basics))
216   (let ((l (make-mutex :name "foo"))
217         (p *current-thread*))
218     (assert (eql (mutex-value l) nil) nil "1")
219     (sb-thread:get-mutex l)
220     (assert (eql (mutex-value l) p) nil "3")
221     (sb-thread:release-mutex l)
222     (assert (eql (mutex-value l) nil) nil "5")))
223
224 (with-test (:name (:with-recursive-lock :basics))
225   (labels ((ours-p (value)
226              (eq *current-thread* value)))
227     (let ((l (make-mutex :name "rec")))
228       (assert (eql (mutex-value l) nil) nil "1")
229       (sb-thread:with-recursive-lock (l)
230         (assert (ours-p (mutex-value l)) nil "3")
231         (sb-thread:with-recursive-lock (l)
232           (assert (ours-p (mutex-value l)) nil "4"))
233         (assert (ours-p (mutex-value l)) nil "5"))
234       (assert (eql (mutex-value l) nil) nil "6"))))
235
236 (with-test (:name (:with-recursive-spinlock :basics))
237   (labels ((ours-p (value)
238              (eq *current-thread* value)))
239     (let ((l (make-spinlock :name "rec")))
240       (assert (eql (spinlock-value l) nil) nil "1")
241       (with-recursive-spinlock (l)
242         (assert (ours-p (spinlock-value l)) nil "3")
243         (with-recursive-spinlock (l)
244           (assert (ours-p (spinlock-value l)) nil "4"))
245         (assert (ours-p (spinlock-value l)) nil "5"))
246       (assert (eql (spinlock-value l) nil) nil "6"))))
247
248 (with-test (:name (:mutex :nesting-mutex-and-recursive-lock))
249   (let ((l (make-mutex :name "a mutex")))
250     (with-mutex (l)
251       (with-recursive-lock (l)))))
252
253 (with-test (:name (:spinlock :nesting-spinlock-and-recursive-spinlock))
254   (let ((l (make-spinlock :name "a spinlock")))
255     (with-spinlock (l)
256       (with-recursive-spinlock (l)))))
257
258 (with-test (:name (:spinlock :more-basics))
259   (let ((l (make-spinlock :name "spinlock")))
260     (assert (eql (spinlock-value l) nil) ((spinlock-value l))
261             "spinlock not free (1)")
262     (with-spinlock (l)
263       (assert (eql (spinlock-value l) *current-thread*) ((spinlock-value l))
264               "spinlock not taken"))
265     (assert (eql (spinlock-value l) nil) ((spinlock-value l))
266             "spinlock not free (2)")))
267
268 ;; test that SLEEP actually sleeps for at least the given time, even
269 ;; if interrupted by another thread exiting/a gc/anything
270 (with-test (:name (:sleep :continue-sleeping-after-interrupt))
271   (let ((start-time (get-universal-time)))
272     (make-thread (lambda () (sleep 1) (sb-ext:gc :full t)))
273     (sleep 5)
274     (assert (>= (get-universal-time) (+ 5 start-time)))))
275
276
277 (with-test (:name (:condition-wait :basics-1))
278   (let ((queue (make-waitqueue :name "queue"))
279         (lock (make-mutex :name "lock"))
280         (n 0))
281     (labels ((in-new-thread ()
282                (with-mutex (lock)
283                  (assert (eql (mutex-value lock) *current-thread*))
284                  (format t "~A got mutex~%" *current-thread*)
285                  ;; now drop it and sleep
286                  (condition-wait queue lock)
287                  ;; after waking we should have the lock again
288                  (assert (eql (mutex-value lock) *current-thread*))
289                  (assert (eql n 1))
290                  (decf n))))
291       (make-thread #'in-new-thread)
292       (sleep 2)            ; give it  a chance to start
293       ;; check the lock is free while it's asleep
294       (format t "parent thread ~A~%" *current-thread*)
295       (assert (eql (mutex-value lock) nil))
296       (with-mutex (lock)
297         (incf n)
298         (condition-notify queue))
299       (sleep 1))))
300
301 (with-test (:name (:condition-wait :basics-2))
302   (let ((queue (make-waitqueue :name "queue"))
303         (lock (make-mutex :name "lock")))
304     (labels ((ours-p (value)
305                (eq *current-thread* value))
306              (in-new-thread ()
307                (with-recursive-lock (lock)
308                  (assert (ours-p (mutex-value lock)))
309                  (format t "~A got mutex~%" (mutex-value lock))
310                  ;; now drop it and sleep
311                  (condition-wait queue lock)
312                  ;; after waking we should have the lock again
313                  (format t "woken, ~A got mutex~%" (mutex-value lock))
314                  (assert (ours-p (mutex-value lock))))))
315       (make-thread #'in-new-thread)
316       (sleep 2)            ; give it  a chance to start
317       ;; check the lock is free while it's asleep
318       (format t "parent thread ~A~%" *current-thread*)
319       (assert (eql (mutex-value lock) nil))
320       (with-recursive-lock (lock)
321         (condition-notify queue))
322       (sleep 1))))
323
324 (with-test (:name (:mutex :contention))
325   (let ((mutex (make-mutex :name "contended")))
326     (labels ((run ()
327                (let ((me *current-thread*))
328                  (dotimes (i 100)
329                    (with-mutex (mutex)
330                      (sleep .03)
331                      (assert (eql (mutex-value mutex) me)))
332                    (assert (not (eql (mutex-value mutex) me))))
333                  (format t "done ~A~%" *current-thread*))))
334       (let ((kid1 (make-thread #'run))
335             (kid2 (make-thread #'run)))
336         (format t "contention ~A ~A~%" kid1 kid2)
337         (wait-for-threads (list kid1 kid2))))))
338
339 ;;; semaphores
340
341 (defmacro raises-timeout-p (&body body)
342   `(handler-case (progn (progn ,@body) nil)
343     (sb-ext:timeout () t)))
344
345 (with-test (:name (:semaphore :wait-forever))
346   (let ((sem (make-semaphore :count 0)))
347     (assert (raises-timeout-p
348               (sb-ext:with-timeout 0.1
349                 (wait-on-semaphore sem))))))
350
351 (with-test (:name (:semaphore :initial-count))
352   (let ((sem (make-semaphore :count 1)))
353     (sb-ext:with-timeout 0.1
354       (wait-on-semaphore sem))))
355
356 (with-test (:name (:semaphore :wait-then-signal))
357   (let ((sem (make-semaphore))
358         (signalled-p nil))
359     (make-thread (lambda ()
360                    (sleep 0.1)
361                    (setq signalled-p t)
362                    (signal-semaphore sem)))
363     (wait-on-semaphore sem)
364     (assert signalled-p)))
365
366 (with-test (:name (:semaphore :signal-then-wait))
367   (let ((sem (make-semaphore))
368         (signalled-p nil))
369     (make-thread (lambda ()
370                    (signal-semaphore sem)
371                    (setq signalled-p t)))
372     (loop until signalled-p)
373     (wait-on-semaphore sem)
374     (assert signalled-p)))
375
376 (defun test-semaphore-multiple-signals (wait-on-semaphore)
377   (let* ((sem (make-semaphore :count 5))
378          (threads (loop repeat 20 collecting
379                         (make-thread (lambda ()
380                                        (funcall wait-on-semaphore sem))))))
381     (flet ((count-live-threads ()
382              (count-if #'thread-alive-p threads)))
383       (sleep 0.5)
384       (assert (= 15 (count-live-threads)))
385       (signal-semaphore sem 10)
386       (sleep 0.5)
387       (assert (= 5 (count-live-threads)))
388       (signal-semaphore sem 3)
389       (sleep 0.5)
390       (assert (= 2 (count-live-threads)))
391       (signal-semaphore sem 4)
392       (sleep 0.5)
393       (assert (= 0 (count-live-threads))))))
394
395 (with-test (:name (:semaphore :multiple-signals))
396   (test-semaphore-multiple-signals #'wait-on-semaphore))
397
398 (with-test (:name (:try-semaphore :trivial-fail))
399   (assert (eq (try-semaphore (make-semaphore :count 0)) 'nil)))
400
401 (with-test (:name (:try-semaphore :trivial-success))
402   (let ((sem (make-semaphore :count 1)))
403     (assert (try-semaphore sem))
404     (assert (zerop (semaphore-count sem)))))
405
406 (with-test (:name (:try-semaphore :trivial-fail :n>1))
407   (assert (eq (try-semaphore (make-semaphore :count 1) 2) 'nil)))
408
409 (with-test (:name (:try-semaphore :trivial-success :n>1))
410   (let ((sem (make-semaphore :count 10)))
411     (assert (try-semaphore sem 5))
412     (assert (try-semaphore sem 5))
413     (assert (zerop (semaphore-count sem)))))
414
415 (with-test (:name (:try-semaphore :emulate-wait-on-semaphore))
416   (flet ((busy-wait-on-semaphore (sem)
417            (loop until (try-semaphore sem) do (sleep 0.001))))
418     (test-semaphore-multiple-signals #'busy-wait-on-semaphore)))
419
420 ;;; Here we test that interrupting TRY-SEMAPHORE does not leave a
421 ;;; semaphore in a bad state.
422 (with-test (:name (:try-semaphore :interrupt-safe))
423   (flet ((make-threads (count fn)
424            (loop repeat count collect (make-thread fn)))
425          (kill-thread (thread)
426            (when (thread-alive-p thread)
427              (ignore-errors (terminate-thread thread))))
428          (count-live-threads (threads)
429            (count-if #'thread-alive-p threads)))
430     ;; WAITERS will already be waiting on the semaphore while
431     ;; threads-being-interrupted will perform TRY-SEMAPHORE on that
432     ;; semaphore, and MORE-WAITERS are new threads trying to wait on
433     ;; the semaphore during the interruption-fire.
434     (let* ((sem (make-semaphore :count 100))
435            (waiters (make-threads 20 #'(lambda ()
436                                          (wait-on-semaphore sem))))
437            (triers  (make-threads 40 #'(lambda ()
438                                          (sleep (random 0.01))
439                                          (try-semaphore sem (1+ (random 5))))))
440            (more-waiters
441             (loop repeat 10
442                   do (kill-thread (nth (random 40) triers))
443                   collect (make-thread #'(lambda () (wait-on-semaphore sem)))
444                   do (kill-thread (nth (random 40) triers)))))
445       (sleep 0.5)
446       ;; Now ensure that the waiting threads will all be waked up,
447       ;; i.e. that the semaphore is still working.
448       (loop repeat (+ (count-live-threads waiters)
449                       (count-live-threads more-waiters))
450             do (signal-semaphore sem))
451       (sleep 0.5)
452       (assert (zerop (count-live-threads triers)))
453       (assert (zerop (count-live-threads waiters)))
454       (assert (zerop (count-live-threads more-waiters))))))
455
456
457
458 (format t "~&semaphore tests done~%")
459
460 (defun test-interrupt (function-to-interrupt &optional quit-p)
461   (let ((child  (make-thread function-to-interrupt)))
462     ;;(format t "gdb ./src/runtime/sbcl ~A~%attach ~A~%" child child)
463     (sleep 2)
464     (format t "interrupting child ~A~%" child)
465     (interrupt-thread child
466                       (lambda ()
467                         (format t "child pid ~A~%" *current-thread*)
468                         (when quit-p (sb-ext:quit))))
469     (sleep 1)
470     child))
471
472 ;; separate tests for (a) interrupting Lisp code, (b) C code, (c) a syscall,
473 ;; (d) waiting on a lock, (e) some code which we hope is likely to be
474 ;; in pseudo-atomic
475
476 (with-test (:name (:interrupt-thread :more-basics))
477   (let ((child (test-interrupt (lambda () (loop)))))
478     (terminate-thread child)))
479
480 (with-test (:name (:interrupt-thread :interrupt-foreign-loop))
481   (test-interrupt #'loop-forever :quit))
482
483 (with-test (:name (:interrupt-thread :interrupt-sleep))
484   (let ((child (test-interrupt (lambda () (loop (sleep 2000))))))
485     (terminate-thread child)
486     (wait-for-threads (list child))))
487
488 (with-test (:name (:interrupt-thread :interrupt-mutex-acquisition))
489   (let ((lock (make-mutex :name "loctite"))
490         child)
491     (with-mutex (lock)
492       (setf child (test-interrupt
493                    (lambda ()
494                      (with-mutex (lock)
495                        (assert (eql (mutex-value lock) *current-thread*)))
496                      (assert (not (eql (mutex-value lock) *current-thread*)))
497                      (sleep 10))))
498       ;;hold onto lock for long enough that child can't get it immediately
499       (sleep 5)
500       (interrupt-thread child (lambda () (format t "l ~A~%" (mutex-value lock))))
501       (format t "parent releasing lock~%"))
502     (terminate-thread child)
503     (wait-for-threads (list child))))
504
505 (format t "~&locking test done~%")
506
507 (defun alloc-stuff () (copy-list '(1 2 3 4 5)))
508
509 (with-test (:name (:interrupt-thread :interrupt-consing-child))
510   (let ((thread (sb-thread:make-thread (lambda () (loop (alloc-stuff))))))
511     (let ((killers
512            (loop repeat 4 collect
513                  (sb-thread:make-thread
514                   (lambda ()
515                     (loop repeat 25 do
516                           (sleep (random 0.1d0))
517                           (princ ".")
518                           (force-output)
519                           (sb-thread:interrupt-thread thread (lambda ()))))))))
520       (wait-for-threads killers)
521       (sb-thread:terminate-thread thread)
522       (wait-for-threads (list thread))))
523   (sb-ext:gc :full t))
524
525 (format t "~&multi interrupt test done~%")
526
527 (with-test (:name (:interrupt-thread :interrupt-consing-child :again))
528   (let ((c (make-thread (lambda () (loop (alloc-stuff))))))
529     ;; NB this only works on x86: other ports don't have a symbol for
530     ;; pseudo-atomic atomicity
531     (dotimes (i 100)
532       (sleep (random 0.1d0))
533       (interrupt-thread c
534                         (lambda ()
535                           (princ ".") (force-output)
536                           (assert (thread-alive-p *current-thread*))
537                           (assert
538                            (not (logbitp 0 SB-KERNEL:*PSEUDO-ATOMIC-BITS*))))))
539     (terminate-thread c)
540     (wait-for-threads (list c))))
541
542 (format t "~&interrupt test done~%")
543
544 (defstruct counter (n 0 :type sb-vm:word))
545 (defvar *interrupt-counter* (make-counter))
546
547 (declaim (notinline check-interrupt-count))
548 (defun check-interrupt-count (i)
549   (declare (optimize (debug 1) (speed 1)))
550   ;; This used to lose if eflags were not restored after an interrupt.
551   (unless (typep i 'fixnum)
552     (error "!!!!!!!!!!!")))
553
554 (with-test (:name (:interrupt-thread :interrupt-ATOMIC-INCF))
555   (let ((c (make-thread
556             (lambda ()
557               (handler-bind ((error #'(lambda (cond)
558                                         (princ cond)
559                                         (sb-debug:backtrace
560                                          most-positive-fixnum))))
561                 (loop (check-interrupt-count
562                        (counter-n *interrupt-counter*))))))))
563     (let ((func (lambda ()
564                   (princ ".")
565                   (force-output)
566                   (sb-ext:atomic-incf (counter-n *interrupt-counter*)))))
567       (setf (counter-n *interrupt-counter*) 0)
568       (dotimes (i 100)
569         (sleep (random 0.1d0))
570         (interrupt-thread c func))
571       (loop until (= (counter-n *interrupt-counter*) 100) do (sleep 0.1))
572       (terminate-thread c)
573       (wait-for-threads (list c)))))
574
575 (format t "~&interrupt count test done~%")
576
577 (defvar *runningp* nil)
578
579 (with-test (:name (:interrupt-thread :no-nesting))
580   (let ((thread (sb-thread:make-thread
581                  (lambda ()
582                    (catch 'xxx
583                      (loop))))))
584     (declare (special runningp))
585     (sleep 0.2)
586     (sb-thread:interrupt-thread thread
587                                 (lambda ()
588                                     (let ((*runningp* t))
589                                       (sleep 1))))
590     (sleep 0.2)
591     (sb-thread:interrupt-thread thread
592                                 (lambda ()
593                                   (throw 'xxx *runningp*)))
594     (assert (not (sb-thread:join-thread thread)))))
595
596 (with-test (:name (:interrupt-thread :nesting))
597   (let ((thread (sb-thread:make-thread
598                  (lambda ()
599                    (catch 'xxx
600                      (loop))))))
601     (declare (special runningp))
602     (sleep 0.2)
603     (sb-thread:interrupt-thread thread
604                                 (lambda ()
605                                   (let ((*runningp* t))
606                                     (sb-sys:with-interrupts
607                                       (sleep 1)))))
608     (sleep 0.2)
609     (sb-thread:interrupt-thread thread
610                                 (lambda ()
611                                   (throw 'xxx *runningp*)))
612     (assert (sb-thread:join-thread thread))))
613
614 (with-test (:name (:two-threads-running-gc))
615   (let (a-done b-done)
616     (make-thread (lambda ()
617                    (dotimes (i 100)
618                      (sb-ext:gc) (princ "\\") (force-output))
619                    (setf a-done t)))
620     (make-thread (lambda ()
621                    (dotimes (i 25)
622                      (sb-ext:gc :full t)
623                      (princ "/") (force-output))
624                    (setf b-done t)))
625     (loop
626       (when (and a-done b-done) (return))
627       (sleep 1))))
628
629 (terpri)
630
631 (defun waste (&optional (n 100000))
632   (loop repeat n do (make-string 16384)))
633
634 (with-test (:name (:one-thread-runs-gc-while-other-conses))
635   (loop for i below 100 do
636         (princ "!")
637         (force-output)
638         (sb-thread:make-thread
639          #'(lambda ()
640              (waste)))
641         (waste)
642         (sb-ext:gc)))
643
644 (terpri)
645
646 (defparameter *aaa* nil)
647 (with-test (:name (:one-thread-runs-gc-while-other-conses :again))
648   (loop for i below 100 do
649         (princ "!")
650         (force-output)
651         (sb-thread:make-thread
652          #'(lambda ()
653              (let ((*aaa* (waste)))
654                (waste))))
655         (let ((*aaa* (waste)))
656           (waste))
657         (sb-ext:gc)))
658
659 (format t "~&gc test done~%")
660
661 ;; this used to deadlock on session-lock
662 (with-test (:name (:no-session-deadlock))
663   (sb-thread:make-thread (lambda () (sb-ext:gc))))
664
665 (defun exercise-syscall (fn reference-errno)
666   (sb-thread:make-thread
667    (lambda ()
668      (loop do
669           (funcall fn)
670           (let ((errno (sb-unix::get-errno)))
671             (sleep (random 0.1d0))
672             (unless (eql errno reference-errno)
673               (format t "Got errno: ~A (~A) instead of ~A~%"
674                       errno
675                       (sb-unix::strerror)
676                       reference-errno)
677               (force-output)
678               (sb-ext:quit :unix-status 1)))))))
679
680 ;; (nanosleep -1 0) does not fail on FreeBSD
681 (with-test (:name (:exercising-concurrent-syscalls))
682   (let* (#-freebsd
683          (nanosleep-errno (progn
684                             (sb-unix:nanosleep -1 0)
685                             (sb-unix::get-errno)))
686          (open-errno (progn
687                        (open "no-such-file"
688                              :if-does-not-exist nil)
689                        (sb-unix::get-errno)))
690          (threads
691           (list
692            #-freebsd
693            (exercise-syscall (lambda () (sb-unix:nanosleep -1 0)) nanosleep-errno)
694            (exercise-syscall (lambda () (open "no-such-file"
695                                               :if-does-not-exist nil))
696                              open-errno)
697            (sb-thread:make-thread (lambda () (loop (sb-ext:gc) (sleep 1)))))))
698     (sleep 10)
699     (princ "terminating threads")
700     (dolist (thread threads)
701       (sb-thread:terminate-thread thread))))
702
703 (format t "~&errno test done~%")
704
705 (with-test (:name (:terminate-thread-restart))
706   (loop repeat 100 do
707         (let ((thread (sb-thread:make-thread (lambda () (sleep 0.1)))))
708           (sb-thread:interrupt-thread
709            thread
710            (lambda ()
711              (assert (find-restart 'sb-thread:terminate-thread)))))))
712
713 (sb-ext:gc :full t)
714
715 (format t "~&thread startup sigmask test done~%")
716
717 (with-test (:name (:debugger-no-hang-on-session-lock-if-interrupted))
718   (sb-debug::enable-debugger)
719   (let* ((main-thread *current-thread*)
720          (interruptor-thread
721           (make-thread (lambda ()
722                          (sleep 2)
723                          (interrupt-thread main-thread
724                                            (lambda ()
725                                              (with-interrupts
726                                                (break))))
727                          (sleep 2)
728                          (interrupt-thread main-thread #'continue))
729                        :name "interruptor")))
730     (with-session-lock (*session*)
731       (sleep 3))
732     (loop while (thread-alive-p interruptor-thread))))
733
734 (format t "~&session lock test done~%")
735
736 ;; expose thread creation races by exiting quickly
737 (with-test (:name (:no-thread-creation-race :light))
738   (sb-thread:make-thread (lambda ())))
739
740 (with-test (:name (:no-thread-creation-race :heavy))
741   (loop repeat 20 do
742         (wait-for-threads
743          (loop for i below 100 collect
744                (sb-thread:make-thread (lambda ()))))))
745
746 (format t "~&creation test done~%")
747
748 ;; interrupt handlers are per-thread with pthreads, make sure the
749 ;; handler installed in one thread is global
750 (with-test (:name (:global-interrupt-handler))
751   (sb-thread:make-thread
752    (lambda ()
753      (sb-ext:run-program "sleep" '("1") :search t :wait nil))))
754
755 ;;;; Binding stack safety
756
757 (defparameter *x* nil)
758 (defparameter *n-gcs-requested* 0)
759 (defparameter *n-gcs-done* 0)
760
761 (let ((counter 0))
762   (defun make-something-big ()
763     (let ((x (make-string 32000)))
764       (incf counter)
765       (let ((counter counter))
766         (sb-ext:finalize x (lambda () (format t " ~S" counter)
767                                    (force-output)))))))
768
769 (defmacro wait-for-gc ()
770   `(progn
771      (incf *n-gcs-requested*)
772      (loop while (< *n-gcs-done* *n-gcs-requested*))))
773
774 (defun send-gc ()
775   (loop until (< *n-gcs-done* *n-gcs-requested*))
776   (format t "G")
777   (force-output)
778   (sb-ext:gc)
779   (incf *n-gcs-done*))
780
781 (defun exercise-binding ()
782   (loop
783    (let ((*x* (make-something-big)))
784      (let ((*x* 42))
785        ;; at this point the binding stack looks like this:
786        ;; NO-TLS-VALUE-MARKER, *x*, SOMETHING, *x*
787        t))
788    (wait-for-gc)
789    ;; sig_stop_for_gc_handler binds FREE_INTERRUPT_CONTEXT_INDEX. By
790    ;; now SOMETHING is gc'ed and the binding stack looks like this: 0,
791    ;; 0, SOMETHING, 0 (because the symbol slots are zeroed on
792    ;; unbinding but values are not).
793    (let ((*x* nil))
794      ;; bump bsp as if a BIND had just started
795      (incf sb-vm::*binding-stack-pointer* 2)
796      (wait-for-gc)
797      (decf sb-vm::*binding-stack-pointer* 2))))
798
799 (with-test (:name (:binding-stack-gc-safety))
800   (let (threads)
801     (unwind-protect
802          (progn
803            (push (sb-thread:make-thread #'exercise-binding) threads)
804            (push (sb-thread:make-thread (lambda ()
805                                           (loop
806                                            (sleep 0.1)
807                                            (send-gc))))
808                  threads)
809            (sleep 4))
810       (mapc #'sb-thread:terminate-thread threads))))
811
812 (format t "~&binding test done~%")
813
814 ;;; HASH TABLES
815
816 (defvar *errors* nil)
817
818 (defun oops (e)
819   (setf *errors* e)
820   (format t "~&oops: ~A in ~S~%" e *current-thread*)
821   (sb-debug:backtrace)
822   (catch 'done))
823
824 (with-test (:name (:unsynchronized-hash-table))
825   ;; We expect a (probable) error here: parellel readers and writers
826   ;; on a hash-table are not expected to work -- but we also don't
827   ;; expect this to corrupt the image.
828   (let* ((hash (make-hash-table))
829          (*errors* nil)
830          (threads (list (sb-thread:make-thread
831                          (lambda ()
832                            (catch 'done
833                              (handler-bind ((serious-condition 'oops))
834                                (loop
835                                  ;;(princ "1") (force-output)
836                                  (setf (gethash (random 100) hash) 'h)))))
837                          :name "writer")
838                         (sb-thread:make-thread
839                          (lambda ()
840                            (catch 'done
841                              (handler-bind ((serious-condition 'oops))
842                                (loop
843                                  ;;(princ "2") (force-output)
844                                  (remhash (random 100) hash)))))
845                          :name "reader")
846                         (sb-thread:make-thread
847                          (lambda ()
848                            (catch 'done
849                              (handler-bind ((serious-condition 'oops))
850                                (loop
851                                  (sleep (random 1.0))
852                                  (sb-ext:gc :full t)))))
853                          :name "collector"))))
854     (unwind-protect
855          (sleep 10)
856       (mapc #'sb-thread:terminate-thread threads))))
857
858 (format t "~&unsynchronized hash table test done~%")
859
860 (with-test (:name (:synchronized-hash-table))
861   (let* ((hash (make-hash-table :synchronized t))
862          (*errors* nil)
863          (threads (list (sb-thread:make-thread
864                          (lambda ()
865                            (catch 'done
866                              (handler-bind ((serious-condition 'oops))
867                                (loop
868                                  ;;(princ "1") (force-output)
869                                  (setf (gethash (random 100) hash) 'h)))))
870                          :name "writer")
871                         (sb-thread:make-thread
872                          (lambda ()
873                            (catch 'done
874                              (handler-bind ((serious-condition 'oops))
875                                (loop
876                                  ;;(princ "2") (force-output)
877                                  (remhash (random 100) hash)))))
878                          :name "reader")
879                         (sb-thread:make-thread
880                          (lambda ()
881                            (catch 'done
882                              (handler-bind ((serious-condition 'oops))
883                                (loop
884                                  (sleep (random 1.0))
885                                  (sb-ext:gc :full t)))))
886                          :name "collector"))))
887     (unwind-protect
888          (sleep 10)
889       (mapc #'sb-thread:terminate-thread threads))
890     (assert (not *errors*))))
891
892 (format t "~&synchronized hash table test done~%")
893
894 (with-test (:name (:hash-table-parallel-readers))
895   (let ((hash (make-hash-table))
896         (*errors* nil))
897     (loop repeat 50
898           do (setf (gethash (random 100) hash) 'xxx))
899     (let ((threads (list (sb-thread:make-thread
900                           (lambda ()
901                             (catch 'done
902                               (handler-bind ((serious-condition 'oops))
903                                 (loop
904                                       until (eq t (gethash (random 100) hash))))))
905                           :name "reader 1")
906                          (sb-thread:make-thread
907                           (lambda ()
908                             (catch 'done
909                               (handler-bind ((serious-condition 'oops))
910                                 (loop
911                                       until (eq t (gethash (random 100) hash))))))
912                           :name "reader 2")
913                          (sb-thread:make-thread
914                           (lambda ()
915                             (catch 'done
916                               (handler-bind ((serious-condition 'oops))
917                                 (loop
918                                       until (eq t (gethash (random 100) hash))))))
919                           :name "reader 3")
920                          (sb-thread:make-thread
921                           (lambda ()
922                             (catch 'done
923                               (handler-bind ((serious-condition 'oops))
924                                (loop
925                                  (sleep (random 1.0))
926                                  (sb-ext:gc :full t)))))
927                           :name "collector"))))
928       (unwind-protect
929            (sleep 10)
930         (mapc #'sb-thread:terminate-thread threads))
931       (assert (not *errors*)))))
932
933 (format t "~&multiple reader hash table test done~%")
934
935 (with-test (:name (:hash-table-single-accessor-parallel-gc))
936   (let ((hash (make-hash-table))
937         (*errors* nil))
938     (let ((threads (list (sb-thread:make-thread
939                           (lambda ()
940                             (handler-bind ((serious-condition 'oops))
941                               (loop
942                                 (let ((n (random 100)))
943                                   (if (gethash n hash)
944                                       (remhash n hash)
945                                       (setf (gethash n hash) 'h))))))
946                           :name "accessor")
947                          (sb-thread:make-thread
948                           (lambda ()
949                             (handler-bind ((serious-condition 'oops))
950                               (loop
951                                 (sleep (random 1.0))
952                                 (sb-ext:gc :full t))))
953                           :name "collector"))))
954       (unwind-protect
955            (sleep 10)
956         (mapc #'sb-thread:terminate-thread threads))
957       (assert (not *errors*)))))
958
959 (format t "~&single accessor hash table test~%")
960
961 #|  ;; a cll post from eric marsden
962 | (defun crash ()
963 |   (setq *debugger-hook*
964 |         (lambda (condition old-debugger-hook)
965 |           (debug:backtrace 10)
966 |           (unix:unix-exit 2)))
967 |   #+live-dangerously
968 |   (mp::start-sigalrm-yield)
969 |   (flet ((roomy () (loop (with-output-to-string (*standard-output*) (room)))))
970 |     (mp:make-process #'roomy)
971 |     (mp:make-process #'roomy)))
972 |#
973
974 ;;; KLUDGE: No deadlines while waiting on lutex-based condition variables. This test
975 ;;; would just hang.
976 #-sb-lutex
977 (with-test (:name (:condition-variable :wait-multiple))
978   (loop repeat 40 do
979         (let ((waitqueue (sb-thread:make-waitqueue :name "Q"))
980               (mutex (sb-thread:make-mutex :name "M"))
981               (failedp nil))
982           (format t ".")
983           (finish-output t)
984           (let ((threads (loop repeat 200
985                                collect
986                                (sb-thread:make-thread
987                                 (lambda ()
988                                   (handler-case
989                                       (sb-sys:with-deadline (:seconds 0.01)
990                                         (sb-thread:with-mutex (mutex)
991                                           (sb-thread:condition-wait waitqueue
992                                                                     mutex)
993                                           (setq failedp t)))
994                                     (sb-sys:deadline-timeout (c)
995                                       (declare (ignore c)))))))))
996             (mapc #'sb-thread:join-thread threads)
997             (assert (not failedp))))))
998
999 (with-test (:name (:condition-variable :notify-multiple))
1000   (flet ((tester (notify-fun)
1001            (let ((queue (make-waitqueue :name "queue"))
1002                  (lock (make-mutex :name "lock"))
1003                  (data nil))
1004              (labels ((test (x)
1005                         (loop
1006                            (with-mutex (lock)
1007                              (format t "condition-wait ~a~%" x)
1008                              (force-output)
1009                              (condition-wait queue lock)
1010                              (format t "woke up ~a~%" x)
1011                              (force-output)
1012                              (push x data)))))
1013                (let ((threads (loop for x from 1 to 10
1014                                     collect
1015                                     (let ((x x))
1016                                       (sb-thread:make-thread (lambda ()
1017                                                                (test x)))))))
1018                  (sleep 5)
1019                  (with-mutex (lock)
1020                    (funcall notify-fun queue))
1021                  (sleep 5)
1022                  (mapcar #'terminate-thread threads)
1023                  ;; Check that all threads woke up at least once
1024                  (assert (= (length (remove-duplicates data)) 10)))))))
1025     (tester (lambda (queue)
1026               (format t "~&(condition-notify queue 10)~%")
1027               (force-output)
1028               (condition-notify queue 10)))
1029     (tester (lambda (queue)
1030               (format t "~&(condition-broadcast queue)~%")
1031               (force-output)
1032               (condition-broadcast queue)))))
1033
1034 (format t "waitqueue wakeup tests done~%")
1035
1036 ;;; Make sure that a deadline handler is not invoked twice in a row in
1037 ;;; CONDITION-WAIT. See LP #512914 for a detailed explanation.
1038 ;;;
1039 #-sb-lutex    ; See KLUDGE above: no deadlines for condition-wait+lutexes.
1040 (with-test (:name (:condition-wait :deadlines :LP-512914))
1041   (let ((n 2) ; was empirically enough to trigger the bug
1042         (mutex (sb-thread:make-mutex))
1043         (waitq (sb-thread:make-waitqueue))
1044         (threads nil)
1045         (deadline-handler-run-twice? nil))
1046     (dotimes (i n)
1047       (let ((child
1048              (sb-thread:make-thread
1049               #'(lambda ()
1050                   (handler-bind
1051                       ((sb-sys:deadline-timeout
1052                         (let ((already? nil))
1053                           #'(lambda (c)
1054                               (when already?
1055                                 (setq deadline-handler-run-twice? t))
1056                               (setq already? t)
1057                               (sleep 0.2)
1058                               (sb-thread:condition-broadcast waitq)
1059                               (sb-sys:defer-deadline 10.0 c)))))
1060                     (sb-sys:with-deadline (:seconds 0.1)
1061                       (sb-thread:with-mutex (mutex)
1062                         (sb-thread:condition-wait waitq mutex))))))))
1063         (push child threads)))
1064     (mapc #'sb-thread:join-thread threads)
1065     (assert (not deadline-handler-run-twice?))))
1066
1067 (with-test (:name (:condition-wait :signal-deadline-with-interrupts-enabled))
1068   (let ((mutex (sb-thread:make-mutex))
1069         (waitq (sb-thread:make-waitqueue))
1070         (A-holds? :unknown)
1071         (B-holds? :unknown)
1072         (A-interrupts-enabled? :unknown)
1073         (B-interrupts-enabled? :unknown)
1074         (A)
1075         (B))
1076     ;; W.L.O.G., we assume that A is executed first...
1077     (setq A (sb-thread:make-thread
1078              #'(lambda ()
1079                  (handler-bind
1080                      ((sb-sys:deadline-timeout
1081                        #'(lambda (c)
1082                            ;; We came here through the call to DECODE-TIMEOUT
1083                            ;; in CONDITION-WAIT; hence both here are supposed
1084                            ;; to evaluate to T.
1085                            (setq A-holds? (sb-thread:holding-mutex-p mutex))
1086                            (setq A-interrupts-enabled?
1087                                  sb-sys:*interrupts-enabled*)
1088                            (sleep 0.2)
1089                            (sb-thread:condition-broadcast waitq)
1090                            (sb-sys:defer-deadline 10.0 c))))
1091                    (sb-sys:with-deadline (:seconds 0.1)
1092                      (sb-thread:with-mutex (mutex)
1093                        (sb-thread:condition-wait waitq mutex)))))))
1094     (setq B (sb-thread:make-thread
1095              #'(lambda ()
1096                  (thread-yield)
1097                  (handler-bind
1098                      ((sb-sys:deadline-timeout
1099                        #'(lambda (c)
1100                            ;; We came here through the call to GET-MUTEX
1101                            ;; in CONDITION-WAIT (contended case of
1102                            ;; reaquiring the mutex) - so the former will
1103                            ;; be NIL, but interrupts should still be enabled.
1104                            (setq B-holds? (sb-thread:holding-mutex-p mutex))
1105                            (setq B-interrupts-enabled?
1106                                  sb-sys:*interrupts-enabled*)
1107                            (sleep 0.2)
1108                            (sb-thread:condition-broadcast waitq)
1109                            (sb-sys:defer-deadline 10.0 c))))
1110                    (sb-sys:with-deadline (:seconds 0.1)
1111                      (sb-thread:with-mutex (mutex)
1112                        (sb-thread:condition-wait waitq mutex)))))))
1113     (sb-thread:join-thread A)
1114     (sb-thread:join-thread B)
1115     (let ((A-result (list A-holds? A-interrupts-enabled?))
1116           (B-result (list B-holds? B-interrupts-enabled?)))
1117       ;; We also check some subtle behaviour w.r.t. whether a deadline
1118       ;; handler in CONDITION-WAIT got the mutex, or not. This is most
1119       ;; probably very internal behaviour (so user should not depend
1120       ;; on it) -- I added the testing here just to manifest current
1121       ;; behaviour.
1122       (cond ((equal A-result '(t t)) (assert (equal B-result '(nil t))))
1123             ((equal B-result '(t t)) (assert (equal A-result '(nil t))))
1124             (t (error "Failure: fall through."))))))
1125
1126 (with-test (:name (:mutex :finalization))
1127   (let ((a nil))
1128     (dotimes (i 500000)
1129       (setf a (make-mutex)))))
1130
1131 (format t "mutex finalization test done~%")
1132
1133 ;;; Check that INFO is thread-safe, at least when we're just doing reads.
1134
1135 (let* ((symbols (loop repeat 10000 collect (gensym)))
1136        (functions (loop for (symbol . rest) on symbols
1137                         for next = (car rest)
1138                         for fun = (let ((next next))
1139                                     (lambda (n)
1140                                       (if next
1141                                           (funcall next (1- n))
1142                                           n)))
1143                         do (setf (symbol-function symbol) fun)
1144                         collect fun)))
1145   (defun infodb-test ()
1146     (funcall (car functions) 9999)))
1147
1148 (with-test (:name (:infodb :read))
1149   (let* ((ok t)
1150          (threads (loop for i from 0 to 10
1151                         collect (sb-thread:make-thread
1152                                  (lambda ()
1153                                    (dotimes (j 100)
1154                                      (write-char #\-)
1155                                      (finish-output)
1156                                      (let ((n (infodb-test)))
1157                                        (unless (zerop n)
1158                                          (setf ok nil)
1159                                          (format t "N != 0 (~A)~%" n)
1160                                          (sb-ext:quit)))))))))
1161     (wait-for-threads threads)
1162     (assert ok)))
1163
1164 (format t "infodb test done~%")
1165
1166 (with-test (:name (:backtrace))
1167   ;; Printing backtraces from several threads at once used to hang the
1168   ;; whole SBCL process (discovered by accident due to a timer.impure
1169   ;; test misbehaving). The cause was that packages weren't even
1170   ;; thread-safe for only doing FIND-SYMBOL, and while printing
1171   ;; backtraces a loot of symbol lookups need to be done due to
1172   ;; *PRINT-ESCAPE*.
1173   (let* ((threads (loop repeat 10
1174                         collect (sb-thread:make-thread
1175                                  (lambda ()
1176                                    (dotimes (i 1000)
1177                                      (with-output-to-string (*debug-io*)
1178                                        (sb-debug::backtrace 10))))))))
1179     (wait-for-threads threads)))
1180
1181 (format t "backtrace test done~%")
1182
1183 (format t "~&starting gc deadlock test: WARNING: THIS TEST WILL HANG ON FAILURE!~%")
1184
1185 (with-test (:name (:gc-deadlock))
1186   ;; Prior to 0.9.16.46 thread exit potentially deadlocked the
1187   ;; GC due to *all-threads-lock* and session lock. On earlier
1188   ;; versions and at least on one specific box this test is good enough
1189   ;; to catch that typically well before the 1500th iteration.
1190   (loop
1191      with i = 0
1192      with n = 3000
1193      while (< i n)
1194      do
1195        (incf i)
1196        (when (zerop (mod i 100))
1197          (write-char #\.)
1198          (force-output))
1199        (handler-case
1200            (if (oddp i)
1201                (sb-thread:make-thread
1202                 (lambda ()
1203                   (sleep (random 0.001)))
1204                 :name (list :sleep i))
1205                (sb-thread:make-thread
1206                 (lambda ()
1207                   ;; KLUDGE: what we are doing here is explicit,
1208                   ;; but the same can happen because of a regular
1209                   ;; MAKE-THREAD or LIST-ALL-THREADS, and various
1210                   ;; session functions.
1211                   (sb-thread::with-all-threads-lock
1212                     (sb-thread::with-session-lock (sb-thread::*session*)
1213                       (sb-ext:gc))))
1214                 :name (list :gc i)))
1215          (error (e)
1216            (format t "~%error creating thread ~D: ~A -- backing off for retry~%" i e)
1217            (sleep 0.1)
1218            (incf i)))))
1219
1220 (format t "~&gc deadlock test done~%")
1221 \f
1222 (let ((count (make-array 8 :initial-element 0)))
1223   (defun closure-one ()
1224     (declare (optimize safety))
1225     (values (incf (aref count 0)) (incf (aref count 1))
1226             (incf (aref count 2)) (incf (aref count 3))
1227             (incf (aref count 4)) (incf (aref count 5))
1228             (incf (aref count 6)) (incf (aref count 7))))
1229   (defun no-optimizing-away-closure-one ()
1230     (setf count (make-array 8 :initial-element 0))))
1231
1232 (defstruct box
1233   (count 0))
1234
1235 (let ((one (make-box))
1236       (two (make-box))
1237       (three (make-box)))
1238   (defun closure-two ()
1239     (declare (optimize safety))
1240     (values (incf (box-count one)) (incf (box-count two)) (incf (box-count three))))
1241   (defun no-optimizing-away-closure-two ()
1242     (setf one (make-box)
1243           two (make-box)
1244           three (make-box))))
1245
1246 (with-test (:name (:funcallable-instances))
1247   ;; the funcallable-instance implementation used not to be threadsafe
1248   ;; against setting the funcallable-instance function to a closure
1249   ;; (because the code and lexenv were set separately).
1250   (let ((fun (sb-kernel:%make-funcallable-instance 0))
1251         (condition nil))
1252     (setf (sb-kernel:funcallable-instance-fun fun) #'closure-one)
1253     (flet ((changer ()
1254              (loop (setf (sb-kernel:funcallable-instance-fun fun) #'closure-one)
1255                    (setf (sb-kernel:funcallable-instance-fun fun) #'closure-two)))
1256            (test ()
1257              (handler-case (loop (funcall fun))
1258                (serious-condition (c) (setf condition c)))))
1259       (let ((changer (make-thread #'changer))
1260             (test (make-thread #'test)))
1261         (handler-case
1262             (progn
1263               ;; The two closures above are fairly carefully crafted
1264               ;; so that if given the wrong lexenv they will tend to
1265               ;; do some serious damage, but it is of course difficult
1266               ;; to predict where the various bits and pieces will be
1267               ;; allocated.  Five seconds failed fairly reliably on
1268               ;; both my x86 and x86-64 systems.  -- CSR, 2006-09-27.
1269               (sb-ext:with-timeout 5
1270                 (wait-for-threads (list test)))
1271               (error "~@<test thread got condition:~2I~_~A~@:>" condition))
1272           (sb-ext:timeout ()
1273             (terminate-thread changer)
1274             (terminate-thread test)
1275             (wait-for-threads (list changer test))))))))
1276
1277 (format t "~&funcallable-instance test done~%")
1278
1279 (defun random-type (n)
1280   `(integer ,(random n) ,(+ n (random n))))
1281
1282 (defun subtypep-hash-cache-test ()
1283   (dotimes (i 10000)
1284     (let ((type1 (random-type 500))
1285           (type2 (random-type 500)))
1286       (let ((a (subtypep type1 type2)))
1287         (dotimes (i 100)
1288           (assert (eq (subtypep type1 type2) a))))))
1289   (format t "ok~%")
1290   (force-output))
1291
1292 (with-test (:name '(:hash-cache :subtypep))
1293   (dotimes (i 10)
1294     (sb-thread:make-thread #'subtypep-hash-cache-test)))
1295 (format t "hash-cache tests done~%")
1296
1297 ;;;; BLACK BOX TESTS
1298
1299 (in-package :cl-user)
1300 (use-package :test-util)
1301 (use-package "ASSERTOID")
1302
1303 (format t "parallel defclass test -- WARNING, WILL HANG ON FAILURE!~%")
1304 (with-test (:name :parallel-defclass)
1305   (defclass test-1 () ((a :initform :orig-a)))
1306   (defclass test-2 () ((b :initform :orig-b)))
1307   (defclass test-3 (test-1 test-2) ((c :initform :orig-c)))
1308   (let* ((run t)
1309          (d1 (sb-thread:make-thread (lambda ()
1310                                       (loop while run
1311                                             do (defclass test-1 () ((a :initform :new-a)))
1312                                             (write-char #\1)
1313                                             (force-output)))
1314                                     :name "d1"))
1315          (d2 (sb-thread:make-thread (lambda ()
1316                                       (loop while run
1317                                             do (defclass test-2 () ((b :initform :new-b)))
1318                                                (write-char #\2)
1319                                                (force-output)))
1320                                     :name "d2"))
1321          (d3 (sb-thread:make-thread (lambda ()
1322                                       (loop while run
1323                                             do (defclass test-3 (test-1 test-2) ((c :initform :new-c)))
1324                                                (write-char #\3)
1325                                                (force-output)))
1326                                     :name "d3"))
1327          (i (sb-thread:make-thread (lambda ()
1328                                      (loop while run
1329                                            do (let ((i (make-instance 'test-3)))
1330                                                 (assert (member (slot-value i 'a) '(:orig-a :new-a)))
1331                                                 (assert (member (slot-value i 'b) '(:orig-b :new-b)))
1332                                                 (assert (member (slot-value i 'c) '(:orig-c :new-c))))
1333                                               (write-char #\i)
1334                                               (force-output)))
1335                                    :name "i")))
1336     (format t "~%sleeping!~%")
1337     (sleep 2.0)
1338     (format t "~%stopping!~%")
1339     (setf run nil)
1340     (mapc (lambda (th)
1341             (sb-thread:join-thread th)
1342             (format t "~%joined ~S~%" (sb-thread:thread-name th)))
1343           (list d1 d2 d3 i))))
1344 (format t "parallel defclass test done~%")