1.0.3.45: added JOIN-THREAD
[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 (in-package "SB-THREAD") ; this is white-box testing, really
15
16 (use-package :test-util)
17 (use-package "ASSERTOID")
18
19 (defun wait-for-threads (threads)
20   (mapc #'sb-thread:join-thread threads)
21   (assert (not (some #'sb-thread:thread-alive-p threads))))
22
23 (assert (eql 1 (length (list-all-threads))))
24
25 (assert (eq *current-thread*
26             (find (thread-name *current-thread*) (list-all-threads)
27                   :key #'thread-name :test #'equal)))
28
29 (assert (thread-alive-p *current-thread*))
30
31 (let ((a 0))
32   (interrupt-thread *current-thread* (lambda () (setq a 1)))
33   (assert (eql a 1)))
34
35 (let ((spinlock (make-spinlock)))
36   (with-spinlock (spinlock)))
37
38 (let ((mutex (make-mutex)))
39   (with-mutex (mutex)
40     mutex))
41
42 #-sb-thread (sb-ext:quit :unix-status 104)
43
44 (let ((old-threads (list-all-threads))
45       (thread (make-thread (lambda ()
46                              (assert (find *current-thread* *all-threads*))
47                              (sleep 2))))
48       (new-threads (list-all-threads)))
49   (assert (thread-alive-p thread))
50   (assert (eq thread (first new-threads)))
51   (assert (= (1+ (length old-threads)) (length new-threads)))
52   (sleep 3)
53   (assert (not (thread-alive-p thread))))
54
55 (with-test (:name '(:join-thread :nlx :default))
56   (let ((sym (gensym)))
57     (assert (eq sym (join-thread (make-thread (lambda () (sb-ext:quit)))
58                                  :default sym)))))
59
60 (with-test (:name '(:join-thread :nlx :error))
61   (raises-error? (join-thread (make-thread (lambda () (sb-ext:quit)))
62                               :errorp t)))
63
64 (with-test (:name '(:join-thread :multiple-values))
65   (assert (equal '(1 2 3)
66                  (multiple-value-list
67                   (join-thread (make-thread (lambda () (values 1 2 3))))))))
68
69 ;;; We had appalling scaling properties for a while.  Make sure they
70 ;;; don't reappear.
71 (defun scaling-test (function &optional (nthreads 5))
72   "Execute FUNCTION with NTHREADS lurking to slow it down."
73   (let ((queue (sb-thread:make-waitqueue))
74         (mutex (sb-thread:make-mutex)))
75     ;; Start NTHREADS idle threads.
76     (dotimes (i nthreads)
77       (sb-thread:make-thread (lambda ()
78                                (with-mutex (mutex)
79                                  (sb-thread:condition-wait queue mutex))
80                                (sb-ext:quit))))
81     (let ((start-time (get-internal-run-time)))
82       (funcall function)
83       (prog1 (- (get-internal-run-time) start-time)
84         (sb-thread:condition-broadcast queue)))))
85 (defun fact (n)
86   "A function that does work with the CPU."
87   (if (zerop n) 1 (* n (fact (1- n)))))
88 (let ((work (lambda () (fact 15000))))
89   (let ((zero (scaling-test work 0))
90         (four (scaling-test work 4)))
91     ;; a slightly weak assertion, but good enough for starters.
92     (assert (< four (* 1.5 zero)))))
93
94 ;;; For one of the interupt-thread tests, we want a foreign function
95 ;;; that does not make syscalls
96
97 (with-open-file (o "threads-foreign.c" :direction :output :if-exists :supersede)
98   (format o "void loop_forever() { while(1) ; }~%"))
99 (sb-ext:run-program
100  #-sunos "cc" #+sunos "gcc"
101  (or #+(or linux freebsd sunos) '(#+x86-64 "-fPIC"
102                                   "-shared" "-o" "threads-foreign.so" "threads-foreign.c")
103      #+darwin '("-dynamiclib" "-o" "threads-foreign.so" "threads-foreign.c")
104      (error "Missing shared library compilation options for this platform"))
105  :search t)
106 (sb-alien:load-shared-object "threads-foreign.so")
107 (sb-alien:define-alien-routine loop-forever sb-alien:void)
108
109
110 ;;; elementary "can we get a lock and release it again"
111 (let ((l (make-mutex :name "foo"))
112       (p *current-thread*))
113   (assert (eql (mutex-value l) nil) nil "1")
114   (sb-thread:get-mutex l)
115   (assert (eql (mutex-value l) p) nil "3")
116   (sb-thread:release-mutex l)
117   (assert (eql (mutex-value l) nil) nil "5"))
118
119 (labels ((ours-p (value)
120            (eq *current-thread* value)))
121   (let ((l (make-mutex :name "rec")))
122     (assert (eql (mutex-value l) nil) nil "1")
123     (sb-thread:with-recursive-lock (l)
124       (assert (ours-p (mutex-value l)) nil "3")
125       (sb-thread:with-recursive-lock (l)
126         (assert (ours-p (mutex-value l)) nil "4"))
127       (assert (ours-p (mutex-value l)) nil "5"))
128     (assert (eql (mutex-value l) nil) nil "6")))
129
130 (with-test (:name (:mutex :nesting-mutex-and-recursive-lock))
131   (let ((l (make-mutex :name "a mutex")))
132     (with-mutex (l)
133       (with-recursive-lock (l)))))
134
135 (let ((l (make-spinlock :name "spinlock")))
136   (assert (eql (spinlock-value l) 0) nil "1")
137   (with-spinlock (l)
138     (assert (eql (spinlock-value l) 1) nil "2"))
139   (assert (eql (spinlock-value l) 0) nil "3"))
140
141 ;; test that SLEEP actually sleeps for at least the given time, even
142 ;; if interrupted by another thread exiting/a gc/anything
143 (let ((start-time (get-universal-time)))
144   (make-thread (lambda () (sleep 1) (sb-ext:gc :full t)))
145   (sleep 5)
146   (assert (>= (get-universal-time) (+ 5 start-time))))
147
148
149 (let ((queue (make-waitqueue :name "queue"))
150       (lock (make-mutex :name "lock"))
151       (n 0))
152   (labels ((in-new-thread ()
153              (with-mutex (lock)
154                (assert (eql (mutex-value lock) *current-thread*))
155                (format t "~A got mutex~%" *current-thread*)
156                ;; now drop it and sleep
157                (condition-wait queue lock)
158                ;; after waking we should have the lock again
159                (assert (eql (mutex-value lock) *current-thread*))
160                (assert (eql n 1))
161                (decf n))))
162     (make-thread #'in-new-thread)
163     (sleep 2)                           ; give it  a chance to start
164     ;; check the lock is free while it's asleep
165     (format t "parent thread ~A~%" *current-thread*)
166     (assert (eql (mutex-value lock) nil))
167     (with-mutex (lock)
168       (incf n)
169       (condition-notify queue))
170     (sleep 1)))
171
172 (let ((queue (make-waitqueue :name "queue"))
173       (lock (make-mutex :name "lock")))
174   (labels ((ours-p (value)
175              (eq *current-thread* value))
176            (in-new-thread ()
177              (with-recursive-lock (lock)
178                (assert (ours-p (mutex-value lock)))
179                (format t "~A got mutex~%" (mutex-value lock))
180                ;; now drop it and sleep
181                (condition-wait queue lock)
182                ;; after waking we should have the lock again
183                (format t "woken, ~A got mutex~%" (mutex-value lock))
184                (assert (ours-p (mutex-value lock))))))
185     (make-thread #'in-new-thread)
186     (sleep 2)                           ; give it  a chance to start
187     ;; check the lock is free while it's asleep
188     (format t "parent thread ~A~%" *current-thread*)
189     (assert (eql (mutex-value lock) nil))
190     (with-recursive-lock (lock)
191       (condition-notify queue))
192     (sleep 1)))
193
194 (let ((mutex (make-mutex :name "contended")))
195   (labels ((run ()
196              (let ((me *current-thread*))
197                (dotimes (i 100)
198                  (with-mutex (mutex)
199                    (sleep .03)
200                    (assert (eql (mutex-value mutex) me)))
201                  (assert (not (eql (mutex-value mutex) me))))
202                (format t "done ~A~%" *current-thread*))))
203     (let ((kid1 (make-thread #'run))
204           (kid2 (make-thread #'run)))
205       (format t "contention ~A ~A~%" kid1 kid2)
206       (wait-for-threads (list kid1 kid2)))))
207
208 ;;; semaphores
209
210 (defmacro raises-timeout-p (&body body)
211   `(handler-case (progn (progn ,@body) nil)
212     (sb-ext:timeout () t)))
213
214 (with-test (:name (:semaphore :wait-forever))
215   (let ((sem (make-semaphore :count 0)))
216     (assert (raises-timeout-p
217               (sb-ext:with-timeout 0.1
218                 (wait-on-semaphore sem))))))
219
220 (with-test (:name (:semaphore :initial-count))
221   (let ((sem (make-semaphore :count 1)))
222     (sb-ext:with-timeout 0.1
223       (wait-on-semaphore sem))))
224
225 (with-test (:name (:semaphore :wait-then-signal))
226   (let ((sem (make-semaphore))
227         (signalled-p nil))
228     (make-thread (lambda ()
229                    (sleep 0.1)
230                    (setq signalled-p t)
231                    (signal-semaphore sem)))
232     (wait-on-semaphore sem)
233     (assert signalled-p)))
234
235 (with-test (:name (:semaphore :signal-then-wait))
236   (let ((sem (make-semaphore))
237         (signalled-p nil))
238     (make-thread (lambda ()
239                    (signal-semaphore sem)
240                    (setq signalled-p t)))
241     (loop until signalled-p)
242     (wait-on-semaphore sem)
243     (assert signalled-p)))
244
245 (with-test (:name (:semaphore :multiple-signals))
246   (let* ((sem (make-semaphore :count 5))
247          (threads (loop repeat 20
248                         collect (make-thread (lambda ()
249                                                (wait-on-semaphore sem))))))
250     (flet ((count-live-threads ()
251              (count-if #'thread-alive-p threads)))
252       (sleep 0.5)
253       (assert (= 15 (count-live-threads)))
254       (signal-semaphore sem 10)
255       (sleep 0.5)
256       (assert (= 5 (count-live-threads)))
257       (signal-semaphore sem 3)
258       (sleep 0.5)
259       (assert (= 2 (count-live-threads)))
260       (signal-semaphore sem 4)
261       (sleep 0.5)
262       (assert (= 0 (count-live-threads))))))
263
264 (format t "~&semaphore tests done~%")
265
266 (defun test-interrupt (function-to-interrupt &optional quit-p)
267   (let ((child  (make-thread function-to-interrupt)))
268     ;;(format t "gdb ./src/runtime/sbcl ~A~%attach ~A~%" child child)
269     (sleep 2)
270     (format t "interrupting child ~A~%" child)
271     (interrupt-thread child
272                       (lambda ()
273                         (format t "child pid ~A~%" *current-thread*)
274                         (when quit-p (sb-ext:quit))))
275     (sleep 1)
276     child))
277
278 ;; separate tests for (a) interrupting Lisp code, (b) C code, (c) a syscall,
279 ;; (d) waiting on a lock, (e) some code which we hope is likely to be
280 ;; in pseudo-atomic
281
282 (let ((child (test-interrupt (lambda () (loop)))))  (terminate-thread child))
283
284 (test-interrupt #'loop-forever :quit)
285
286 (let ((child (test-interrupt (lambda () (loop (sleep 2000))))))
287   (terminate-thread child)
288   (wait-for-threads (list child)))
289
290 (let ((lock (make-mutex :name "loctite"))
291       child)
292   (with-mutex (lock)
293     (setf child (test-interrupt
294                  (lambda ()
295                    (with-mutex (lock)
296                      (assert (eql (mutex-value lock) *current-thread*)))
297                    (assert (not (eql (mutex-value lock) *current-thread*)))
298                    (sleep 10))))
299     ;;hold onto lock for long enough that child can't get it immediately
300     (sleep 5)
301     (interrupt-thread child (lambda () (format t "l ~A~%" (mutex-value lock))))
302     (format t "parent releasing lock~%"))
303   (terminate-thread child)
304   (wait-for-threads (list child)))
305
306 (format t "~&locking test done~%")
307
308 (defun alloc-stuff () (copy-list '(1 2 3 4 5)))
309
310 (progn
311   (let ((thread (sb-thread:make-thread (lambda () (loop (alloc-stuff))))))
312     (let ((killers
313            (loop repeat 4 collect
314                  (sb-thread:make-thread
315                   (lambda ()
316                     (loop repeat 25 do
317                           (sleep (random 0.1d0))
318                           (princ ".")
319                           (force-output)
320                           (sb-thread:interrupt-thread thread (lambda ()))))))))
321       (wait-for-threads killers)
322       (sb-thread:terminate-thread thread)
323       (wait-for-threads (list thread))))
324   (sb-ext:gc :full t))
325
326 (format t "~&multi interrupt test done~%")
327
328 (let ((c (make-thread (lambda () (loop (alloc-stuff))))))
329   ;; NB this only works on x86: other ports don't have a symbol for
330   ;; pseudo-atomic atomicity
331   (dotimes (i 100)
332     (sleep (random 0.1d0))
333     (interrupt-thread c
334                       (lambda ()
335                         (princ ".") (force-output)
336                         (assert (thread-alive-p *current-thread*))
337                         (assert
338                          (not (logbitp 0 SB-KERNEL:*PSEUDO-ATOMIC-BITS*))))))
339   (terminate-thread c)
340   (wait-for-threads (list c)))
341
342 (format t "~&interrupt test done~%")
343
344 (defparameter *interrupt-count* 0)
345
346 (declaim (notinline check-interrupt-count))
347 (defun check-interrupt-count (i)
348   (declare (optimize (debug 1) (speed 1)))
349   ;; This used to lose if eflags were not restored after an interrupt.
350   (unless (typep i 'fixnum)
351     (error "!!!!!!!!!!!")))
352
353 (let ((c (make-thread
354           (lambda ()
355             (handler-bind ((error #'(lambda (cond)
356                                       (princ cond)
357                                       (sb-debug:backtrace
358                                        most-positive-fixnum))))
359               (loop (check-interrupt-count *interrupt-count*)))))))
360   (let ((func (lambda ()
361                 (princ ".")
362                 (force-output)
363                 (sb-impl::atomic-incf/symbol *interrupt-count*))))
364     (setq *interrupt-count* 0)
365     (dotimes (i 100)
366       (sleep (random 0.1d0))
367       (interrupt-thread c func))
368     (loop until (= *interrupt-count* 100) do (sleep 0.1))
369     (terminate-thread c)
370     (wait-for-threads (list c))))
371
372 (format t "~&interrupt count test done~%")
373
374 (let (a-done b-done)
375   (make-thread (lambda ()
376                  (dotimes (i 100)
377                    (sb-ext:gc) (princ "\\") (force-output))
378                  (setf a-done t)))
379   (make-thread (lambda ()
380                  (dotimes (i 25)
381                    (sb-ext:gc :full t)
382                    (princ "/") (force-output))
383                  (setf b-done t)))
384   (loop
385    (when (and a-done b-done) (return))
386    (sleep 1)))
387
388 (terpri)
389
390 (defun waste (&optional (n 100000))
391   (loop repeat n do (make-string 16384)))
392
393 (loop for i below 100 do
394       (princ "!")
395       (force-output)
396       (sb-thread:make-thread
397        #'(lambda ()
398            (waste)))
399       (waste)
400       (sb-ext:gc))
401
402 (terpri)
403
404 (defparameter *aaa* nil)
405 (loop for i below 100 do
406       (princ "!")
407       (force-output)
408       (sb-thread:make-thread
409        #'(lambda ()
410            (let ((*aaa* (waste)))
411              (waste))))
412       (let ((*aaa* (waste)))
413         (waste))
414       (sb-ext:gc))
415
416 (format t "~&gc test done~%")
417
418 ;; this used to deadlock on session-lock
419 (sb-thread:make-thread (lambda () (sb-ext:gc)))
420 ;; expose thread creation races by exiting quickly
421 (sb-thread:make-thread (lambda ()))
422
423 (defun exercise-syscall (fn reference-errno)
424   (sb-thread:make-thread
425    (lambda ()
426      (loop do
427           (funcall fn)
428           (let ((errno (sb-unix::get-errno)))
429             (sleep (random 0.1d0))
430             (unless (eql errno reference-errno)
431               (format t "Got errno: ~A (~A) instead of ~A~%"
432                       errno
433                       (sb-unix::strerror)
434                       reference-errno)
435               (force-output)
436               (sb-ext:quit :unix-status 1)))))))
437
438 ;; (nanosleep -1 0) does not fail on FreeBSD
439 (let* (#-freebsd
440        (nanosleep-errno (progn
441                           (sb-unix:nanosleep -1 0)
442                           (sb-unix::get-errno)))
443        (open-errno (progn
444                      (open "no-such-file"
445                            :if-does-not-exist nil)
446                      (sb-unix::get-errno)))
447        (threads
448         (list
449          #-freebsd
450          (exercise-syscall (lambda () (sb-unix:nanosleep -1 0)) nanosleep-errno)
451          (exercise-syscall (lambda () (open "no-such-file"
452                                             :if-does-not-exist nil))
453                            open-errno)
454          (sb-thread:make-thread (lambda () (loop (sb-ext:gc) (sleep 1)))))))
455   (sleep 10)
456   (princ "terminating threads")
457   (dolist (thread threads)
458     (sb-thread:terminate-thread thread)))
459
460 (format t "~&errno test done~%")
461
462 (loop repeat 100 do
463       (let ((thread (sb-thread:make-thread (lambda () (sleep 0.1)))))
464         (sb-thread:interrupt-thread
465          thread
466          (lambda ()
467            (assert (find-restart 'sb-thread:terminate-thread))))))
468
469 (sb-ext:gc :full t)
470
471 (format t "~&thread startup sigmask test done~%")
472
473 (sb-debug::enable-debugger)
474 (let* ((main-thread *current-thread*)
475        (interruptor-thread
476         (make-thread (lambda ()
477                        (sleep 2)
478                        (interrupt-thread main-thread #'break)
479                        (sleep 2)
480                        (interrupt-thread main-thread #'continue)))))
481   (with-session-lock (*session*)
482     (sleep 3))
483   (loop while (thread-alive-p interruptor-thread)))
484
485 (format t "~&session lock test done~%")
486
487 (loop repeat 20 do
488       (wait-for-threads
489        (loop for i below 100 collect
490              (sb-thread:make-thread (lambda ())))))
491
492 (format t "~&creation test done~%")
493
494 ;; interrupt handlers are per-thread with pthreads, make sure the
495 ;; handler installed in one thread is global
496 (sb-thread:make-thread
497  (lambda ()
498    (sb-ext:run-program "sleep" '("1") :search t :wait nil)))
499
500 ;;;; Binding stack safety
501
502 (defparameter *x* nil)
503 (defparameter *n-gcs-requested* 0)
504 (defparameter *n-gcs-done* 0)
505
506 (let ((counter 0))
507   (defun make-something-big ()
508     (let ((x (make-string 32000)))
509       (incf counter)
510       (let ((counter counter))
511         (sb-ext:finalize x (lambda () (format t " ~S" counter)
512                                    (force-output)))))))
513
514 (defmacro wait-for-gc ()
515   `(progn
516      (incf *n-gcs-requested*)
517      (loop while (< *n-gcs-done* *n-gcs-requested*))))
518
519 (defun send-gc ()
520   (loop until (< *n-gcs-done* *n-gcs-requested*))
521   (format t "G")
522   (force-output)
523   (sb-ext:gc)
524   (incf *n-gcs-done*))
525
526 (defun exercise-binding ()
527   (loop
528    (let ((*x* (make-something-big)))
529      (let ((*x* 42))
530        ;; at this point the binding stack looks like this:
531        ;; NO-TLS-VALUE-MARKER, *x*, SOMETHING, *x*
532        t))
533    (wait-for-gc)
534    ;; sig_stop_for_gc_handler binds FREE_INTERRUPT_CONTEXT_INDEX. By
535    ;; now SOMETHING is gc'ed and the binding stack looks like this: 0,
536    ;; 0, SOMETHING, 0 (because the symbol slots are zeroed on
537    ;; unbinding but values are not).
538    (let ((*x* nil))
539      ;; bump bsp as if a BIND had just started
540      (incf sb-vm::*binding-stack-pointer* 2)
541      (wait-for-gc)
542      (decf sb-vm::*binding-stack-pointer* 2))))
543
544 (with-test (:name (:binding-stack-gc-safety))
545   (let (threads)
546     (unwind-protect
547          (progn
548            (push (sb-thread:make-thread #'exercise-binding) threads)
549            (push (sb-thread:make-thread (lambda ()
550                                           (loop
551                                            (sleep 0.1)
552                                            (send-gc))))
553                  threads)
554            (sleep 4))
555       (mapc #'sb-thread:terminate-thread threads))))
556
557 (format t "~&binding test done~%")
558
559 ;; Try to corrupt the NEXT-VECTOR. Operations on a hash table with a
560 ;; cyclic NEXT-VECTOR can loop endlessly in a WITHOUT-GCING form
561 ;; causing the next gc hang SBCL.
562 (with-test (:name (:hash-table-thread-safety))
563   (let* ((hash (make-hash-table))
564          (threads (list (sb-thread:make-thread
565                          (lambda ()
566                            (loop
567                             ;;(princ "1") (force-output)
568                             (setf (gethash (random 100) hash) 'h))))
569                         (sb-thread:make-thread
570                          (lambda ()
571                            (loop
572                             ;;(princ "2") (force-output)
573                             (remhash (random 100) hash))))
574                         (sb-thread:make-thread
575                          (lambda ()
576                            (loop
577                             (sleep (random 1.0))
578                             (sb-ext:gc :full t)))))))
579     (unwind-protect
580          (sleep 5)
581       (mapc #'sb-thread:terminate-thread threads))))
582
583 (format t "~&hash table test done~%")
584 #|  ;; a cll post from eric marsden
585 | (defun crash ()
586 |   (setq *debugger-hook*
587 |         (lambda (condition old-debugger-hook)
588 |           (debug:backtrace 10)
589 |           (unix:unix-exit 2)))
590 |   #+live-dangerously
591 |   (mp::start-sigalrm-yield)
592 |   (flet ((roomy () (loop (with-output-to-string (*standard-output*) (room)))))
593 |     (mp:make-process #'roomy)
594 |     (mp:make-process #'roomy)))
595 |#
596
597 (with-test (:name (:condition-variable :notify-multiple))
598   (flet ((tester (notify-fun)
599            (let ((queue (make-waitqueue :name "queue"))
600                  (lock (make-mutex :name "lock"))
601                  (data nil))
602              (labels ((test (x)
603                         (loop
604                            (with-mutex (lock)
605                              (format t "condition-wait ~a~%" x)
606                              (force-output)
607                              (condition-wait queue lock)
608                              (format t "woke up ~a~%" x)
609                              (force-output)
610                              (push x data)))))
611                (let ((threads (loop for x from 1 to 10
612                                     collect
613                                     (let ((x x))
614                                       (sb-thread:make-thread (lambda ()
615                                                                (test x)))))))
616                  (sleep 5)
617                  (with-mutex (lock)
618                    (funcall notify-fun queue))
619                  (sleep 5)
620                  (mapcar #'terminate-thread threads)
621                  ;; Check that all threads woke up at least once
622                  (assert (= (length (remove-duplicates data)) 10)))))))
623     (tester (lambda (queue)
624               (format t "~&(condition-notify queue 10)~%")
625               (force-output)
626               (condition-notify queue 10)))
627     (tester (lambda (queue)
628               (format t "~&(condition-broadcast queue)~%")
629               (force-output)
630               (condition-broadcast queue)))))
631
632 (format t "waitqueue wakeup tests done~%")
633
634 (with-test (:name (:mutex :finalization))
635   (let ((a nil))
636     (dotimes (i 500000)
637       (setf a (make-mutex)))))
638
639 (format t "mutex finalization test done~%")
640
641 ;;; Check that INFO is thread-safe, at least when we're just doing reads.
642
643 (let* ((symbols (loop repeat 10000 collect (gensym)))
644        (functions (loop for (symbol . rest) on symbols
645                         for next = (car rest)
646                         for fun = (let ((next next))
647                                     (lambda (n)
648                                       (if next
649                                           (funcall next (1- n))
650                                           n)))
651                         do (setf (symbol-function symbol) fun)
652                         collect fun)))
653   (defun infodb-test ()
654     (funcall (car functions) 9999)))
655
656 (with-test (:name (:infodb :read))
657   (let* ((ok t)
658          (threads (loop for i from 0 to 10
659                         collect (sb-thread:make-thread
660                                  (lambda ()
661                                    (dotimes (j 100)
662                                      (write-char #\-)
663                                      (finish-output)
664                                      (let ((n (infodb-test)))
665                                        (unless (zerop n)
666                                          (setf ok nil)
667                                          (format t "N != 0 (~A)~%" n)
668                                          (sb-ext:quit)))))))))
669     (wait-for-threads threads)
670     (assert ok)))
671
672 (format t "infodb test done~%")
673
674 (with-test (:name (:backtrace))
675   ;; Printing backtraces from several threads at once used to hang the
676   ;; whole SBCL process (discovered by accident due to a timer.impure
677   ;; test misbehaving). The cause was that packages weren't even
678   ;; thread-safe for only doing FIND-SYMBOL, and while printing
679   ;; backtraces a loot of symbol lookups need to be done due to
680   ;; *PRINT-ESCAPE*.
681   (let* ((threads (loop repeat 10
682                         collect (sb-thread:make-thread
683                                  (lambda ()
684                                    (dotimes (i 1000)
685                                      (with-output-to-string (*debug-io*)
686                                        (sb-debug::backtrace 10))))))))
687     (wait-for-threads threads)))
688
689 (format t "backtrace test done~%")
690
691 (format t "~&starting gc deadlock test: WARNING: THIS TEST WILL HANG ON FAILURE!~%")
692
693 (with-test (:name (:gc-deadlock))
694   ;; Prior to 0.9.16.46 thread exit potentially deadlocked the
695   ;; GC due to *all-threads-lock* and session lock. On earlier
696   ;; versions and at least on one specific box this test is good enough
697   ;; to catch that typically well before the 1500th iteration.
698   (loop
699      with i = 0
700      with n = 3000
701      while (< i n)
702      do
703        (incf i)
704        (when (zerop (mod i 100))
705          (write-char #\.)
706          (force-output))
707        (handler-case
708            (if (oddp i)
709                (sb-thread:make-thread
710                 (lambda ()
711                   (sleep (random 0.001)))
712                 :name (list :sleep i))
713                (sb-thread:make-thread
714                 (lambda ()
715                   ;; KLUDGE: what we are doing here is explicit,
716                   ;; but the same can happen because of a regular
717                   ;; MAKE-THREAD or LIST-ALL-THREADS, and various
718                   ;; session functions.
719                   (sb-thread:with-mutex (sb-thread::*all-threads-lock*)
720                     (sb-thread::with-session-lock (sb-thread::*session*)
721                       (sb-ext:gc))))
722                 :name (list :gc i)))
723          (error (e)
724            (format t "~%error creating thread ~D: ~A -- backing off for retry~%" i e)
725            (sleep 0.1)
726            (incf i)))))
727
728 (format t "~&gc deadlock test done~%")
729 \f
730 (let ((count (make-array 8 :initial-element 0)))
731   (defun closure-one ()
732     (declare (optimize safety))
733     (values (incf (aref count 0)) (incf (aref count 1))
734             (incf (aref count 2)) (incf (aref count 3))
735             (incf (aref count 4)) (incf (aref count 5))
736             (incf (aref count 6)) (incf (aref count 7))))
737   (defun no-optimizing-away-closure-one ()
738     (setf count (make-array 8 :initial-element 0))))
739
740 (defstruct box
741   (count 0))
742
743 (let ((one (make-box))
744       (two (make-box))
745       (three (make-box)))
746   (defun closure-two ()
747     (declare (optimize safety))
748     (values (incf (box-count one)) (incf (box-count two)) (incf (box-count three))))
749   (defun no-optimizing-away-closure-two ()
750     (setf one (make-box)
751           two (make-box)
752           three (make-box))))
753
754 (with-test (:name (:funcallable-instances))
755   ;; the funcallable-instance implementation used not to be threadsafe
756   ;; against setting the funcallable-instance function to a closure
757   ;; (because the code and lexenv were set separately).
758   (let ((fun (sb-kernel:%make-funcallable-instance 0))
759         (condition nil))
760     (setf (sb-kernel:funcallable-instance-fun fun) #'closure-one)
761     (flet ((changer ()
762              (loop (setf (sb-kernel:funcallable-instance-fun fun) #'closure-one)
763                    (setf (sb-kernel:funcallable-instance-fun fun) #'closure-two)))
764            (test ()
765              (handler-case (loop (funcall fun))
766                (serious-condition (c) (setf condition c)))))
767       (let ((changer (make-thread #'changer))
768             (test (make-thread #'test)))
769         (handler-case
770             (progn
771               ;; The two closures above are fairly carefully crafted
772               ;; so that if given the wrong lexenv they will tend to
773               ;; do some serious damage, but it is of course difficult
774               ;; to predict where the various bits and pieces will be
775               ;; allocated.  Five seconds failed fairly reliably on
776               ;; both my x86 and x86-64 systems.  -- CSR, 2006-09-27.
777               (sb-ext:with-timeout 5
778                 (wait-for-threads (list test)))
779               (error "~@<test thread got condition:~2I~_~A~@:>" condition))
780           (sb-ext:timeout ()
781             (terminate-thread changer)
782             (terminate-thread test)
783             (wait-for-threads (list changer test))))))))
784
785 (format t "~&funcallable-instance test done~%")
786
787 (defun random-type (n)
788   `(integer ,(random n) ,(+ n (random n))))
789
790 (defun subtypep-hash-cache-test ()
791   (dotimes (i 10000)
792     (let ((type1 (random-type 500))
793           (type2 (random-type 500)))
794       (let ((a (subtypep type1 type2)))
795         (dotimes (i 100)
796           (assert (eq (subtypep type1 type2) a))))))
797   (format t "ok~%")
798   (force-output))
799
800 (with-test (:name '(:hash-cache :subtypep))
801   (dotimes (i 10)
802     (sb-thread:make-thread #'subtypep-hash-cache-test)))
803
804 (format t "hash-cache tests done~%")