0.9.6.48: more stability
[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
18 (defun wait-for-threads (threads)
19   (loop while (some #'sb-thread:thread-alive-p threads) do (sleep 0.01)))
20
21 (assert (eql 1 (length (list-all-threads))))
22
23 (assert (eq *current-thread*
24             (find (thread-name *current-thread*) (list-all-threads)
25                   :key #'thread-name :test #'equal)))
26
27 (assert (thread-alive-p *current-thread*))
28
29 (let ((a 0))
30   (interrupt-thread *current-thread* (lambda () (setq a 1)))
31   (assert (eql a 1)))
32
33 (let ((spinlock (make-spinlock)))
34   (with-spinlock (spinlock)))
35
36 (let ((mutex (make-mutex)))
37   (with-mutex (mutex)
38     mutex))
39
40 #-sb-thread (sb-ext:quit :unix-status 104)
41
42 (let ((old-threads (list-all-threads))
43       (thread (make-thread (lambda ()
44                              (assert (find *current-thread* *all-threads*))
45                              (sleep 2))))
46       (new-threads (list-all-threads)))
47   (assert (thread-alive-p thread))
48   (assert (eq thread (first new-threads)))
49   (assert (= (1+ (length old-threads)) (length new-threads)))
50   (sleep 3)
51   (assert (not (thread-alive-p thread))))
52
53 ;;; We had appalling scaling properties for a while.  Make sure they
54 ;;; don't reappear.
55 (defun scaling-test (function &optional (nthreads 5))
56   "Execute FUNCTION with NTHREADS lurking to slow it down."
57   (let ((queue (sb-thread:make-waitqueue))
58         (mutex (sb-thread:make-mutex)))
59     ;; Start NTHREADS idle threads.
60     (dotimes (i nthreads)
61       (sb-thread:make-thread (lambda ()
62                                (with-mutex (mutex)
63                                  (sb-thread:condition-wait queue mutex))
64                                (sb-ext:quit))))
65     (let ((start-time (get-internal-run-time)))
66       (funcall function)
67       (prog1 (- (get-internal-run-time) start-time)
68         (sb-thread:condition-broadcast queue)))))
69 (defun fact (n)
70   "A function that does work with the CPU."
71   (if (zerop n) 1 (* n (fact (1- n)))))
72 (let ((work (lambda () (fact 15000))))
73   (let ((zero (scaling-test work 0))
74         (four (scaling-test work 4)))
75     ;; a slightly weak assertion, but good enough for starters.
76     (assert (< four (* 1.5 zero)))))
77
78 ;;; For one of the interupt-thread tests, we want a foreign function
79 ;;; that does not make syscalls
80
81 (with-open-file (o "threads-foreign.c" :direction :output :if-exists :supersede)
82   (format o "void loop_forever() { while(1) ; }~%"))
83 (sb-ext:run-program
84  "cc"
85  (or #+linux '("-shared" "-o" "threads-foreign.so" "threads-foreign.c")
86      (error "Missing shared library compilation options for this platform"))
87  :search t)
88 (sb-alien:load-shared-object "threads-foreign.so")
89 (sb-alien:define-alien-routine loop-forever sb-alien:void)
90
91
92 ;;; elementary "can we get a lock and release it again"
93 (let ((l (make-mutex :name "foo"))
94       (p *current-thread*))
95   (assert (eql (mutex-value l) nil) nil "1")
96   (sb-thread:get-mutex l)
97   (assert (eql (mutex-value l) p) nil "3")
98   (sb-thread:release-mutex l)
99   (assert (eql (mutex-value l) nil) nil "5"))
100
101 (labels ((ours-p (value)
102            (eq *current-thread* value)))
103   (let ((l (make-mutex :name "rec")))
104     (assert (eql (mutex-value l) nil) nil "1")
105     (sb-thread:with-recursive-lock (l)
106       (assert (ours-p (mutex-value l)) nil "3")
107       (sb-thread:with-recursive-lock (l)
108         (assert (ours-p (mutex-value l)) nil "4"))
109       (assert (ours-p (mutex-value l)) nil "5"))
110     (assert (eql (mutex-value l) nil) nil "6")))
111
112 (with-test (:name (:mutex :nesting-mutex-and-recursive-lock))
113   (let ((l (make-mutex :name "a mutex")))
114     (with-mutex (l)
115       (with-recursive-lock (l)))))
116
117 (let ((l (make-spinlock :name "spinlock"))
118       (p *current-thread*))
119   (assert (eql (spinlock-value l) 0) nil "1")
120   (with-spinlock (l)
121     (assert (eql (spinlock-value l) p) nil "2"))
122   (assert (eql (spinlock-value l) 0) nil "3"))
123
124 ;; test that SLEEP actually sleeps for at least the given time, even
125 ;; if interrupted by another thread exiting/a gc/anything
126 (let ((start-time (get-universal-time)))
127   (make-thread (lambda () (sleep 1) (sb-ext:gc :full t)))
128   (sleep 5)
129   (assert (>= (get-universal-time) (+ 5 start-time))))
130
131
132 (let ((queue (make-waitqueue :name "queue"))
133       (lock (make-mutex :name "lock"))
134       (n 0))
135   (labels ((in-new-thread ()
136              (with-mutex (lock)
137                (assert (eql (mutex-value lock) *current-thread*))
138                (format t "~A got mutex~%" *current-thread*)
139                ;; now drop it and sleep
140                (condition-wait queue lock)
141                ;; after waking we should have the lock again
142                (assert (eql (mutex-value lock) *current-thread*))
143                (assert (eql n 1))
144                (decf n))))
145     (make-thread #'in-new-thread)
146     (sleep 2)                           ; give it  a chance to start
147     ;; check the lock is free while it's asleep
148     (format t "parent thread ~A~%" *current-thread*)
149     (assert (eql (mutex-value lock) nil))
150     (with-mutex (lock)
151       (incf n)
152       (condition-notify queue))
153     (sleep 1)))
154
155 (let ((queue (make-waitqueue :name "queue"))
156       (lock (make-mutex :name "lock")))
157   (labels ((ours-p (value)
158              (eq *current-thread* value))
159            (in-new-thread ()
160              (with-recursive-lock (lock)
161                (assert (ours-p (mutex-value lock)))
162                (format t "~A got mutex~%" (mutex-value lock))
163                ;; now drop it and sleep
164                (condition-wait queue lock)
165                ;; after waking we should have the lock again
166                (format t "woken, ~A got mutex~%" (mutex-value lock))
167                (assert (ours-p (mutex-value lock))))))
168     (make-thread #'in-new-thread)
169     (sleep 2)                           ; give it  a chance to start
170     ;; check the lock is free while it's asleep
171     (format t "parent thread ~A~%" *current-thread*)
172     (assert (eql (mutex-value lock) nil))
173     (with-recursive-lock (lock)
174       (condition-notify queue))
175     (sleep 1)))
176
177 (let ((mutex (make-mutex :name "contended")))
178   (labels ((run ()
179              (let ((me *current-thread*))
180                (dotimes (i 100)
181                  (with-mutex (mutex)
182                    (sleep .03)
183                    (assert (eql (mutex-value mutex) me)))
184                  (assert (not (eql (mutex-value mutex) me))))
185                (format t "done ~A~%" *current-thread*))))
186     (let ((kid1 (make-thread #'run))
187           (kid2 (make-thread #'run)))
188       (format t "contention ~A ~A~%" kid1 kid2)
189       (wait-for-threads (list kid1 kid2)))))
190
191 ;;; semaphores
192
193 (defmacro raises-timeout-p (&body body)
194   `(handler-case (progn (progn ,@body) nil)
195     (sb-ext:timeout () t)))
196
197 (with-test (:name (:semaphore :wait-forever))
198   (let ((sem (make-semaphore :count 0)))
199     (assert (raises-timeout-p
200               (sb-ext:with-timeout 0.1
201                 (wait-on-semaphore sem))))))
202
203 (with-test (:name (:semaphore :initial-count))
204   (let ((sem (make-semaphore :count 1)))
205     (sb-ext:with-timeout 0.1
206       (wait-on-semaphore sem))))
207
208 (with-test (:name (:semaphore :wait-then-signal))
209   (let ((sem (make-semaphore))
210         (signalled-p nil))
211     (make-thread (lambda ()
212                    (sleep 0.1)
213                    (setq signalled-p t)
214                    (signal-semaphore sem)))
215     (wait-on-semaphore sem)
216     (assert signalled-p)))
217
218 (with-test (:name (:semaphore :signal-then-wait))
219   (let ((sem (make-semaphore))
220         (signalled-p nil))
221     (make-thread (lambda ()
222                    (signal-semaphore sem)
223                    (setq signalled-p t)))
224     (loop until signalled-p)
225     (wait-on-semaphore sem)
226     (assert signalled-p)))
227
228 (with-test (:name (:semaphore :multiple-signals))
229   (let* ((sem (make-semaphore :count 5))
230          (threads (loop repeat 20
231                         collect (make-thread (lambda ()
232                                                (wait-on-semaphore sem))))))
233     (flet ((count-live-threads ()
234              (count-if #'thread-alive-p threads)))
235       (sleep 0.5)
236       (assert (= 15 (count-live-threads)))
237       (signal-semaphore sem 10)
238       (sleep 0.5)
239       (assert (= 5 (count-live-threads)))
240       (signal-semaphore sem 3)
241       (sleep 0.5)
242       (assert (= 2 (count-live-threads)))
243       (signal-semaphore sem 4)
244       (sleep 0.5)
245       (assert (= 0 (count-live-threads))))))
246
247 (format t "~&semaphore tests done~%")
248
249 (defun test-interrupt (function-to-interrupt &optional quit-p)
250   (let ((child  (make-thread function-to-interrupt)))
251     ;;(format t "gdb ./src/runtime/sbcl ~A~%attach ~A~%" child child)
252     (sleep 2)
253     (format t "interrupting child ~A~%" child)
254     (interrupt-thread child
255                       (lambda ()
256                         (format t "child pid ~A~%" *current-thread*)
257                         (when quit-p (sb-ext:quit))))
258     (sleep 1)
259     child))
260
261 ;; separate tests for (a) interrupting Lisp code, (b) C code, (c) a syscall,
262 ;; (d) waiting on a lock, (e) some code which we hope is likely to be
263 ;; in pseudo-atomic
264
265 (let ((child (test-interrupt (lambda () (loop)))))  (terminate-thread child))
266
267 (test-interrupt #'loop-forever :quit)
268
269 (let ((child (test-interrupt (lambda () (loop (sleep 2000))))))
270   (terminate-thread child)
271   (wait-for-threads (list child)))
272
273 (let ((lock (make-mutex :name "loctite"))
274       child)
275   (with-mutex (lock)
276     (setf child (test-interrupt
277                  (lambda ()
278                    (with-mutex (lock)
279                      (assert (eql (mutex-value lock) *current-thread*)))
280                    (assert (not (eql (mutex-value lock) *current-thread*)))
281                    (sleep 10))))
282     ;;hold onto lock for long enough that child can't get it immediately
283     (sleep 5)
284     (interrupt-thread child (lambda () (format t "l ~A~%" (mutex-value lock))))
285     (format t "parent releasing lock~%"))
286   (terminate-thread child)
287   (wait-for-threads (list child)))
288
289 (format t "~&locking test done~%")
290
291 (defun alloc-stuff () (copy-list '(1 2 3 4 5)))
292
293 (progn
294   (let ((thread (sb-thread:make-thread (lambda () (loop (alloc-stuff))))))
295     (let ((killers
296            (loop repeat 4 collect
297                  (sb-thread:make-thread
298                   (lambda ()
299                     (loop repeat 25 do
300                           (sleep (random 0.1d0))
301                           (princ ".")
302                           (force-output)
303                           (sb-thread:interrupt-thread thread (lambda ()))))))))
304       (wait-for-threads killers)
305       (sb-thread:terminate-thread thread)
306       (wait-for-threads (list thread))))
307   (sb-ext:gc :full t))
308
309 (format t "~&multi interrupt test done~%")
310
311 (let ((c (make-thread (lambda () (loop (alloc-stuff))))))
312   ;; NB this only works on x86: other ports don't have a symbol for
313   ;; pseudo-atomic atomicity
314   (dotimes (i 100)
315     (sleep (random 0.1d0))
316     (interrupt-thread c
317                       (lambda ()
318                         (princ ".") (force-output)
319                         (assert (thread-alive-p *current-thread*))
320                         (assert (zerop SB-KERNEL:*PSEUDO-ATOMIC-ATOMIC*)))))
321   (terminate-thread c)
322   (wait-for-threads (list c)))
323
324 (format t "~&interrupt test done~%")
325
326 (defparameter *interrupt-count* 0)
327
328 (declaim (notinline check-interrupt-count))
329 (defun check-interrupt-count (i)
330   (declare (optimize (debug 1) (speed 1)))
331   ;; This used to lose if eflags were not restored after an interrupt.
332   (unless (typep i 'fixnum)
333     (error "!!!!!!!!!!!")))
334
335 (let ((c (make-thread
336           (lambda ()
337             (handler-bind ((error #'(lambda (cond)
338                                       (princ cond)
339                                       (sb-debug:backtrace
340                                        most-positive-fixnum))))
341               (loop (check-interrupt-count *interrupt-count*)))))))
342   (let ((func (lambda ()
343                 (princ ".")
344                 (force-output)
345                 (sb-impl::atomic-incf/symbol *interrupt-count*))))
346     (setq *interrupt-count* 0)
347     (dotimes (i 100)
348       (sleep (random 0.1d0))
349       (interrupt-thread c func))
350     (loop until (= *interrupt-count* 100) do (sleep 0.1))
351     (terminate-thread c)
352     (wait-for-threads (list c))))
353
354 (format t "~&interrupt count test done~%")
355
356 (let (a-done b-done)
357   (make-thread (lambda ()
358                  (dotimes (i 100)
359                    (sb-ext:gc) (princ "\\") (force-output))
360                  (setf a-done t)))
361   (make-thread (lambda ()
362                  (dotimes (i 25)
363                    (sb-ext:gc :full t)
364                    (princ "/") (force-output))
365                  (setf b-done t)))
366   (loop
367    (when (and a-done b-done) (return))
368    (sleep 1)))
369
370 (terpri)
371
372 (defun waste (&optional (n 100000))
373   (loop repeat n do (make-string 16384)))
374
375 (loop for i below 100 do
376       (princ "!")
377       (force-output)
378       (sb-thread:make-thread
379        #'(lambda ()
380            (waste)))
381       (waste)
382       (sb-ext:gc))
383
384 (terpri)
385
386 (defparameter *aaa* nil)
387 (loop for i below 100 do
388       (princ "!")
389       (force-output)
390       (sb-thread:make-thread
391        #'(lambda ()
392            (let ((*aaa* (waste)))
393              (waste))))
394       (let ((*aaa* (waste)))
395         (waste))
396       (sb-ext:gc))
397
398 (format t "~&gc test done~%")
399
400 ;; this used to deadlock on session-lock
401 (sb-thread:make-thread (lambda () (sb-ext:gc)))
402 ;; expose thread creation races by exiting quickly
403 (sb-thread:make-thread (lambda ()))
404
405 (defun exercise-syscall (fn reference-errno)
406   (sb-thread:make-thread
407    (lambda ()
408      (loop do
409           (funcall fn)
410           (let ((errno (sb-unix::get-errno)))
411             (sleep (random 0.1d0))
412             (unless (eql errno reference-errno)
413               (format t "Got errno: ~A (~A) instead of ~A~%"
414                       errno
415                       (sb-unix::strerror)
416                       reference-errno)
417               (force-output)
418               (sb-ext:quit :unix-status 1)))))))
419
420 (let* ((nanosleep-errno (progn
421                           (sb-unix:nanosleep -1 0)
422                           (sb-unix::get-errno)))
423        (open-errno (progn
424                      (open "no-such-file"
425                            :if-does-not-exist nil)
426                      (sb-unix::get-errno)))
427        (threads
428         (list
429          (exercise-syscall (lambda () (sb-unix:nanosleep -1 0)) nanosleep-errno)
430          (exercise-syscall (lambda () (open "no-such-file"
431                                             :if-does-not-exist nil))
432                            open-errno)
433          (sb-thread:make-thread (lambda () (loop (sb-ext:gc) (sleep 1)))))))
434   (sleep 10)
435   (princ "terminating threads")
436   (dolist (thread threads)
437     (sb-thread:terminate-thread thread)))
438
439 (format t "~&errno test done~%")
440
441 (loop repeat 100 do
442       (let ((thread (sb-thread:make-thread (lambda () (sleep 0.1)))))
443         (sb-thread:interrupt-thread
444          thread
445          (lambda ()
446            (assert (find-restart 'sb-thread:terminate-thread))))))
447
448 (sb-ext:gc :full t)
449
450 (format t "~&thread startup sigmask test done~%")
451
452 (sb-debug::enable-debugger)
453 (let* ((main-thread *current-thread*)
454        (interruptor-thread
455         (make-thread (lambda ()
456                        (sleep 2)
457                        (interrupt-thread main-thread #'break)
458                        (sleep 2)
459                        (interrupt-thread main-thread #'continue)))))
460   (with-session-lock (*session*)
461     (sleep 3))
462   (loop while (thread-alive-p interruptor-thread)))
463
464 (format t "~&session lock test done~%")
465
466 (loop repeat 20 do
467       (wait-for-threads
468        (loop for i below 100 collect
469              (sb-thread:make-thread (lambda ())))))
470
471 (format t "~&creation test done~%")
472
473 ;; interrupt handlers are per-thread with pthreads, make sure the
474 ;; handler installed in one thread is global
475 (sb-thread:make-thread
476  (lambda ()
477    (sb-ext:run-program "sleep" '("1") :search t :wait nil)))
478
479 ;;;; Binding stack safety
480
481 (defparameter *x* nil)
482 (defparameter *n-gcs-requested* 0)
483 (defparameter *n-gcs-done* 0)
484
485 (let ((counter 0))
486   (defun make-something-big ()
487     (let ((x (make-string 32000)))
488       (incf counter)
489       (let ((counter counter))
490         (sb-ext:finalize x (lambda () (format t " ~S" counter)
491                                    (force-output)))))))
492
493 (defmacro wait-for-gc ()
494   `(progn
495      (incf *n-gcs-requested*)
496      (loop while (< *n-gcs-done* *n-gcs-requested*))))
497
498 (defun send-gc ()
499   (loop until (< *n-gcs-done* *n-gcs-requested*))
500   (format t "G" *n-gcs-requested* *n-gcs-done*)
501   (force-output)
502   (sb-ext:gc)
503   (incf *n-gcs-done*))
504
505 (defun exercise-binding ()
506   (loop
507    (let ((*x* (make-something-big)))
508      (let ((*x* 42))
509        ;; at this point the binding stack looks like this:
510        ;; NO-TLS-VALUE-MARKER, *x*, SOMETHING, *x*
511        t))
512    (wait-for-gc)
513    ;; sig_stop_for_gc_handler binds FREE_INTERRUPT_CONTEXT_INDEX. By
514    ;; now SOMETHING is gc'ed and the binding stack looks like this: 0,
515    ;; 0, SOMETHING, 0 (because the symbol slots are zeroed on
516    ;; unbinding but values are not).
517    (let ((*x* nil))
518      ;; bump bsp as if a BIND had just started
519      (incf sb-vm::*binding-stack-pointer* 2)
520      (wait-for-gc)
521      (decf sb-vm::*binding-stack-pointer* 2))))
522
523 (with-test (:name (:binding-stack-gc-safety))
524   (let (threads)
525     (unwind-protect
526          (progn
527            (push (sb-thread:make-thread #'exercise-binding) threads)
528            (push (sb-thread:make-thread (lambda ()
529                                           (loop
530                                            (send-gc))))
531                  threads)
532            (sleep 4))
533       (mapc #'sb-thread:terminate-thread threads))))
534
535 (format t "~&binding test done~%")
536
537
538 #|  ;; a cll post from eric marsden
539 | (defun crash ()
540 |   (setq *debugger-hook*
541 |         (lambda (condition old-debugger-hook)
542 |           (debug:backtrace 10)
543 |           (unix:unix-exit 2)))
544 |   #+live-dangerously
545 |   (mp::start-sigalrm-yield)
546 |   (flet ((roomy () (loop (with-output-to-string (*standard-output*) (room)))))
547 |     (mp:make-process #'roomy)
548 |     (mp:make-process #'roomy)))
549 |#