enable previously-broken thread tests on Darwin
[sbcl.git] / tests / threads.pure.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 :cl-user)
15
16 (defpackage :thread-test
17   (:use :cl :sb-thread))
18
19 (in-package :thread-test)
20
21 (use-package :test-util)
22
23 (with-test (:name mutex-owner)
24   ;; Make sure basics are sane on unithreaded ports as well
25   (let ((mutex (make-mutex)))
26     (get-mutex mutex)
27     (assert (eq *current-thread* (mutex-value mutex)))
28     (handler-bind ((warning #'error))
29       (release-mutex mutex))
30     (assert (not (mutex-value mutex)))))
31
32 ;;; Terminating a thread that's waiting for the terminal.
33
34 #+sb-thread
35 (let ((thread (make-thread (lambda ()
36                              (sb-thread::get-foreground)))))
37   (sleep 1)
38   (assert (thread-alive-p thread))
39   (terminate-thread thread)
40   (sleep 1)
41   (assert (not (thread-alive-p thread))))
42
43 ;;; Condition-wait should not be interruptible under WITHOUT-INTERRUPTS
44
45 (with-test (:name without-interrupts+condition-wait
46             :skipped-on '(not :sb-thread))
47   (let* ((lock (make-mutex))
48          (queue (make-waitqueue))
49          (thread (make-thread (lambda ()
50                                 (sb-sys:without-interrupts
51                                   (with-mutex (lock)
52                                     (condition-wait queue lock)))))))
53     (sleep 1)
54     (assert (thread-alive-p thread))
55     (terminate-thread thread)
56     (sleep 1)
57     (assert (thread-alive-p thread))
58     (condition-notify queue)
59     (sleep 1)
60     (assert (not (thread-alive-p thread)))))
61
62 ;;; GET-MUTEX should not be interruptible under WITHOUT-INTERRUPTS
63
64 (with-test (:name without-interrupts+get-mutex :skipped-on '(not :sb-thread))
65   (let* ((lock (make-mutex))
66          (bar (progn (get-mutex lock) nil))
67          (thread (make-thread (lambda ()
68                                 (sb-sys:without-interrupts
69                                     (with-mutex (lock)
70                                       (setf bar t)))))))
71     (sleep 1)
72     (assert (thread-alive-p thread))
73     (terminate-thread thread)
74     (sleep 1)
75     (assert (thread-alive-p thread))
76     (release-mutex lock)
77     (sleep 1)
78     (assert (not (thread-alive-p thread)))
79     (assert (eq :aborted (join-thread thread :default :aborted)))
80     (assert bar)))
81
82 (with-test (:name parallel-find-class :skipped-on '(not :sb-thread))
83   (let* ((oops nil)
84          (threads (loop repeat 10
85                         collect (make-thread (lambda ()
86                                                (handler-case
87                                                    (loop repeat 10000
88                                                          do (find-class (gensym) nil))
89                                                  (serious-condition ()
90                                                    (setf oops t))))))))
91     (mapcar #'sb-thread:join-thread threads)
92     (assert (not oops))))
93
94 (with-test (:name :semaphore-multiple-waiters :skipped-on '(not :sb-thread))
95   (let ((semaphore (make-semaphore :name "test sem")))
96     (labels ((make-readers (n i)
97                (values
98                 (loop for r from 0 below n
99                       collect
100                       (sb-thread:make-thread
101                        (lambda ()
102                          (let ((sem semaphore))
103                            (dotimes (s i)
104                              (sb-thread:wait-on-semaphore sem))))
105                        :name "reader"))
106                 (* n i)))
107              (make-writers (n readers i)
108                (let ((j (* readers i)))
109                  (multiple-value-bind (k rem) (truncate j n)
110                    (values
111                     (let ((writers
112                            (loop for w from 0 below n
113                                  collect
114                                  (sb-thread:make-thread
115                                   (lambda ()
116                                     (let ((sem semaphore))
117                                       (dotimes (s k)
118                                         (sb-thread:signal-semaphore sem))))
119                                   :name "writer"))))
120                       (assert (zerop rem))
121                       writers)
122                     (+ rem (* n k))))))
123              (test (r w n)
124                (multiple-value-bind (readers x) (make-readers r n)
125                  (assert (= (length readers) r))
126                  (multiple-value-bind (writers y) (make-writers w r n)
127                    (assert (= (length writers) w))
128                    (assert (= x y))
129                    (mapc #'sb-thread:join-thread writers)
130                    (mapc #'sb-thread:join-thread readers)
131                    (assert (zerop (sb-thread:semaphore-count semaphore)))
132                    (values)))))
133       (assert
134        (eq :ok
135            (handler-case
136                (sb-ext:with-timeout 10
137                  (test 1 1 100)
138                  (test 2 2 10000)
139                  (test 4 2 10000)
140                  (test 4 2 10000)
141                  (test 10 10 10000)
142                  (test 10 1 10000)
143                  :ok)
144              (sb-ext:timeout ()
145                :timeout)))))))
146
147 ;;;; Printing waitqueues
148
149 (with-test (:name :waitqueue-circle-print :skipped-on '(not :sb-thread))
150   (let* ((*print-circle* nil)
151          (lock (sb-thread:make-mutex))
152          (wq (sb-thread:make-waitqueue)))
153     (sb-thread:with-recursive-lock (lock)
154       (sb-thread:condition-notify wq))
155     ;; Used to blow stack due to recursive structure.
156     (assert (princ-to-string wq))))
157
158 ;;;; SYMBOL-VALUE-IN-THREAD
159
160 (with-test (:name symbol-value-in-thread.1)
161   (let ((* (cons t t)))
162     (assert (eq * (symbol-value-in-thread '* *current-thread*)))
163     (setf (symbol-value-in-thread '* *current-thread*) 123)
164     (assert (= 123 (symbol-value-in-thread '* *current-thread*)))
165     (assert (= 123 *))))
166
167 (with-test (:name symbol-value-in-thread.2 :skipped-on '(not :sb-thread))
168   (let* ((parent *current-thread*)
169          (semaphore (make-semaphore))
170          (child (make-thread (lambda ()
171                                (wait-on-semaphore semaphore)
172                                (let ((old (symbol-value-in-thread 'this-is-new parent)))
173                                  (setf (symbol-value-in-thread 'this-is-new parent) :from-child)
174                                  old)))))
175     (progv '(this-is-new) '(42)
176       (signal-semaphore semaphore)
177       (assert (= 42 (join-thread child)))
178       (assert (eq :from-child (symbol-value 'this-is-new))))))
179
180 ;;; Disabled on Darwin due to deadlocks caused by apparent OS specific deadlocks,
181 ;;; wich _appear_ to be caused by malloc() and free() not being thread safe: an
182 ;;; interrupted malloc in one thread can apparently block a free in another.
183 (with-test (:name symbol-value-in-thread.3
184             :skipped-on '(not :sb-thread))
185   (let* ((parent *current-thread*)
186          (semaphore (make-semaphore))
187          (running t)
188          (noise (make-thread (lambda ()
189                                (loop while running
190                                      do (setf * (make-array 1024))
191                                      ;; Busy-wait a bit so we don't TOTALLY flood the
192                                      ;; system with GCs: a GC occurring in the middle of
193                                      ;; S-V-I-T causes it to start over -- we want that
194                                      ;; to occur occasionally, but not _all_ the time.
195                                         (loop repeat (random 128)
196                                               do (setf ** *)))))))
197     (write-string "; ")
198     (dotimes (i 15000)
199       (when (zerop (mod i 200))
200         (write-char #\.)
201         (force-output))
202       (let* ((mom-mark (cons t t))
203              (kid-mark (cons t t))
204              (child (make-thread (lambda ()
205                                    (wait-on-semaphore semaphore)
206                                    (let ((old (symbol-value-in-thread 'this-is-new parent)))
207                                      (setf (symbol-value-in-thread 'this-is-new parent)
208                                            (make-array 24 :initial-element kid-mark))
209                                      old)))))
210         (progv '(this-is-new) (list (make-array 24 :initial-element mom-mark))
211           (signal-semaphore semaphore)
212           (assert (eq mom-mark (aref (join-thread child) 0)))
213           (assert (eq kid-mark (aref (symbol-value 'this-is-new) 0))))))
214     (setf running nil)
215     (join-thread noise)))
216
217 (with-test (:name symbol-value-in-thread.4 :skipped-on '(not :sb-thread))
218   (let* ((parent *current-thread*)
219          (semaphore (make-semaphore))
220          (child (make-thread (lambda ()
221                                (wait-on-semaphore semaphore)
222                                (symbol-value-in-thread 'this-is-new parent nil)))))
223     (signal-semaphore semaphore)
224     (assert (equal '(nil nil) (multiple-value-list (join-thread child))))))
225
226 (with-test (:name symbol-value-in-thread.5 :skipped-on '(not :sb-thread))
227   (let* ((parent *current-thread*)
228          (semaphore (make-semaphore))
229          (child (make-thread (lambda ()
230                                (wait-on-semaphore semaphore)
231                                (handler-case
232                                    (symbol-value-in-thread 'this-is-new parent)
233                                  (symbol-value-in-thread-error (e)
234                                    (list (thread-error-thread e)
235                                          (cell-error-name e)
236                                          (sb-thread::symbol-value-in-thread-error-info e))))))))
237     (signal-semaphore semaphore)
238     (assert (equal (list *current-thread* 'this-is-new (list :read :unbound-in-thread))
239                    (join-thread child)))))
240
241 (with-test (:name symbol-value-in-thread.6 :skipped-on '(not :sb-thread))
242   (let* ((parent *current-thread*)
243          (semaphore (make-semaphore))
244          (name (gensym))
245          (child (make-thread (lambda ()
246                                (wait-on-semaphore semaphore)
247                                (handler-case
248                                    (setf (symbol-value-in-thread name parent) t)
249                                  (symbol-value-in-thread-error (e)
250                                    (list (thread-error-thread e)
251                                          (cell-error-name e)
252                                          (sb-thread::symbol-value-in-thread-error-info e))))))))
253     (signal-semaphore semaphore)
254     (let ((res (join-thread child))
255           (want (list *current-thread* name (list :write :no-tls-value))))
256       (unless (equal res want)
257         (error "wanted ~S, got ~S" want res)))))
258
259 (with-test (:name symbol-value-in-thread.7 :skipped-on '(not :sb-thread))
260   (let ((child (make-thread (lambda ())))
261         (error-occurred nil))
262     (join-thread child)
263     (handler-case
264         (symbol-value-in-thread 'this-is-new child)
265       (symbol-value-in-thread-error (e)
266         (setf error-occurred t)
267         (assert (eq child (thread-error-thread e)))
268         (assert (eq 'this-is-new (cell-error-name e)))
269         (assert (equal (list :read :thread-dead)
270                        (sb-thread::symbol-value-in-thread-error-info e)))))
271     (assert error-occurred)))
272
273 (with-test (:name symbol-value-in-thread.8  :skipped-on '(not :sb-thread))
274   (let ((child (make-thread (lambda ())))
275         (error-occurred nil))
276     (join-thread child)
277     (handler-case
278         (setf (symbol-value-in-thread 'this-is-new child) t)
279       (symbol-value-in-thread-error (e)
280         (setf error-occurred t)
281         (assert (eq child (thread-error-thread e)))
282         (assert (eq 'this-is-new (cell-error-name e)))
283         (assert (equal (list :write :thread-dead)
284                        (sb-thread::symbol-value-in-thread-error-info e)))))
285     (assert error-occurred)))
286
287 (with-test (:name deadlock-detection.1  :skipped-on '(not :sb-thread))
288   (loop
289     repeat 1000
290     do (flet ((test (ma mb sa sb)
291                 (lambda ()
292                   (handler-case
293                       (sb-thread:with-mutex (ma)
294                         (sb-thread:signal-semaphore sa)
295                         (sb-thread:wait-on-semaphore sb)
296                         (sb-thread:with-mutex (mb)
297                           :ok))
298                     (sb-thread:thread-deadlock (e)
299                       (princ e)
300                       :deadlock)))))
301          (let* ((m1 (sb-thread:make-mutex :name "M1"))
302                 (m2 (sb-thread:make-mutex :name "M2"))
303                 (s1 (sb-thread:make-semaphore :name "S1"))
304                 (s2 (sb-thread:make-semaphore :name "S2"))
305                 (t1 (sb-thread:make-thread (test m1 m2 s1 s2) :name "T1"))
306                 (t2 (sb-thread:make-thread (test m2 m1 s2 s1) :name "T2")))
307            ;; One will deadlock, and the other will then complete normally.
308            (let ((res (list (sb-thread:join-thread t1)
309                             (sb-thread:join-thread t2))))
310              (assert (or (equal '(:deadlock :ok) res)
311                          (equal '(:ok :deadlock) res))))))))
312
313 (with-test (:name deadlock-detection.2 :skipped-on '(not :sb-thread))
314   (let* ((m1 (sb-thread:make-mutex :name "M1"))
315          (m2 (sb-thread:make-mutex :name "M2"))
316          (s1 (sb-thread:make-semaphore :name "S1"))
317          (s2 (sb-thread:make-semaphore :name "S2"))
318          (t1 (sb-thread:make-thread
319               (lambda ()
320                 (sb-thread:with-mutex (m1)
321                   (sb-thread:signal-semaphore s1)
322                   (sb-thread:wait-on-semaphore s2)
323                   (sb-thread:with-mutex (m2)
324                     :ok)))
325               :name "T1")))
326     (prog (err)
327      :retry
328        (handler-bind ((sb-thread:thread-deadlock
329                        (lambda (e)
330                          (unless err
331                            ;; Make sure we can print the condition
332                            ;; while it's active
333                            (let ((*print-circle* nil))
334                              (setf err (princ-to-string e)))
335                            (go :retry)))))
336          (when err
337            (sleep 1))
338          (assert (eq :ok (sb-thread:with-mutex (m2)
339                            (unless err
340                              (sb-thread:signal-semaphore s2)
341                              (sb-thread:wait-on-semaphore s1)
342                              (sleep 1))
343                            (sb-thread:with-mutex (m1)
344                              :ok)))))
345        (assert (stringp err)))
346     (assert (eq :ok (sb-thread:join-thread t1)))))
347
348 (with-test (:name deadlock-detection.3  :skipped-on '(not :sb-thread))
349   (let* ((m1 (sb-thread:make-mutex :name "M1"))
350          (m2 (sb-thread:make-mutex :name "M2"))
351          (s1 (sb-thread:make-semaphore :name "S1"))
352          (s2 (sb-thread:make-semaphore :name "S2"))
353          (t1 (sb-thread:make-thread
354               (lambda ()
355                 (sb-thread:with-mutex (m1)
356                   (sb-thread:signal-semaphore s1)
357                   (sb-thread:wait-on-semaphore s2)
358                   (sb-thread:with-mutex (m2)
359                     :ok)))
360               :name "T1")))
361     ;; Currently we don't consider it a deadlock
362     ;; if there is a timeout in the chain.
363     (assert (eq :deadline
364                 (handler-case
365                     (sb-thread:with-mutex (m2)
366                       (sb-thread:signal-semaphore s2)
367                       (sb-thread:wait-on-semaphore s1)
368                       (sleep 1)
369                       (sb-sys:with-deadline (:seconds 0.1)
370                         (sb-thread:with-mutex (m1)
371                           :ok)))
372                   (sb-sys:deadline-timeout ()
373                     :deadline)
374                   (sb-thread:thread-deadlock ()
375                     :deadlock))))
376     (assert (eq :ok (join-thread t1)))))
377
378 #+sb-thread
379 (with-test (:name :pass-arguments-to-thread)
380   (assert (= 3 (join-thread (make-thread #'+ :arguments '(1 2))))))
381
382 #+sb-thread
383 (with-test (:name :pass-atom-to-thread)
384   (assert (= 1/2 (join-thread (make-thread #'/ :arguments 2)))))
385
386 #+sb-thread
387 (with-test (:name :pass-nil-to-thread)
388   (assert (= 1 (join-thread (make-thread #'* :arguments '())))))
389
390 #+sb-thread
391 (with-test (:name :pass-nothing-to-thread)
392   (assert (= 1 (join-thread (make-thread #'*)))))
393
394 #+sb-thread
395 (with-test (:name :pass-improper-list-to-thread)
396   (multiple-value-bind (value error)
397       (ignore-errors (make-thread #'+ :arguments '(1 . 1)))
398     (when value
399       (join-thread value))
400     (assert (and (null value)
401                  error))))
402
403 (with-test (:name (:wait-for :basics))
404   (assert (not (sb-ext:wait-for nil :timeout 0.1)))
405   (assert (eql 42 (sb-ext:wait-for 42)))
406   (let ((n 0))
407     (assert (eql 100 (sb-ext:wait-for (when (= 100 (incf n))
408                                         n))))))
409
410 (with-test (:name (:wait-for :deadline))
411   (assert (eq :ok
412               (sb-sys:with-deadline (:seconds 10)
413                 (assert (not (sb-ext:wait-for nil :timeout 0.1)))
414                 :ok)))
415   (assert (eq :deadline
416               (handler-case
417                   (sb-sys:with-deadline (:seconds 0.1)
418                     (sb-ext:wait-for nil :timeout 10)
419                     (error "oops"))
420                 (sb-sys:deadline-timeout () :deadline)))))
421
422 (with-test (:name (:condition-wait :timeout :one-thread))
423   (let ((mutex (make-mutex))
424         (waitqueue (make-waitqueue)))
425     (assert (not (with-mutex (mutex)
426                    (condition-wait waitqueue mutex :timeout 0.01))))))
427
428 (with-test (:name (:condition-wait :timeout :many-threads)
429             :skipped-on '(not :sb-thread))
430   (let* ((mutex (make-mutex))
431          (waitqueue (make-waitqueue))
432          (sem (make-semaphore))
433          (data nil)
434          (workers
435            (loop repeat 100
436                  collect (make-thread
437                           (lambda ()
438                             (wait-on-semaphore sem)
439                             (block thread
440                               (with-mutex (mutex)
441                                 (loop until data
442                                       do (or (condition-wait waitqueue mutex :timeout 0.01)
443                                              (return-from thread nil)))
444                                 (assert (eq t (pop data)))
445                                 t)))))))
446     (loop repeat 50
447           do (with-mutex (mutex)
448                (push t data)
449                (condition-notify waitqueue)))
450     (signal-semaphore sem 100)
451     (let ((ok (count-if #'join-thread workers)))
452       (unless (eql 50 ok)
453         (error "Wanted 50, got ~S" ok)))))
454
455 (with-test (:name (:wait-on-semaphore :timeout :one-thread))
456   (let ((sem (make-semaphore))
457         (n 0))
458     (signal-semaphore sem 10)
459     (loop repeat 100
460           do (when (wait-on-semaphore sem :timeout 0.001)
461                (incf n)))
462     (assert (= n 10))))
463
464 (with-test (:name (:wait-on-semaphore :timeout :many-threads)
465             :skipped-on '(not :sb-thread))
466   (let* ((sem (make-semaphore))
467          (threads
468            (progn
469              (signal-semaphore sem 10)
470              (loop repeat 100
471                    collect (make-thread
472                             (lambda ()
473                               (sleep (random 0.02))
474                               (wait-on-semaphore sem :timeout 0.01)))))))
475     (loop repeat 5
476           do (signal-semaphore sem 2))
477     (let ((ok (count-if #'join-thread threads)))
478       (unless (eql 20 ok)
479         (error "Wanted 20, got ~S" ok)))))
480
481 (with-test (:name (:join-thread :timeout)
482             :skipped-on '(not :sb-thread))
483   (assert (eq :error
484               (handler-case
485                   (join-thread (make-thread (lambda () (sleep 10))) :timeout 0.01)
486                 (join-thread-error ()
487                   :error))))
488   (let ((cookie (cons t t)))
489     (assert (eq cookie
490                 (join-thread (make-thread (lambda () (sleep 10)))
491                              :timeout 0.01
492                              :default cookie)))))
493
494 (with-test (:name (:semaphore-notification :wait-on-semaphore)
495             :skipped-on '(not :sb-thread))
496   (let ((sem (make-semaphore))
497         (ok nil)
498         (n 0))
499     (flet ((critical ()
500              (let ((note (make-semaphore-notification)))
501                (sb-sys:without-interrupts
502                  (unwind-protect
503                       (progn
504                         (sb-sys:with-local-interrupts
505                           (wait-on-semaphore sem :notification note)
506                           (sleep (random 0.1)))
507                         (incf n))
508                    ;; Re-increment on exit if we decremented it.
509                    (when (semaphore-notification-status note)
510                      (signal-semaphore sem))
511                    ;; KLUDGE: Prevent interrupts after this point from
512                    ;; unwinding us, so that we can reason about the counts.
513                    #+sb-thread
514                    (sb-thread::block-deferrable-signals))))))
515       (let* ((threads (loop for i from 1 upto 100
516                             collect (make-thread #'critical :name (format nil "T~A" i))))
517              (safe nil)
518              (unsafe nil)
519              (interruptor (make-thread (lambda ()
520                                          (loop until ok)
521                                          (let (x)
522                                            (dolist (thread threads)
523                                              (cond (x
524                                                     (push thread unsafe)
525                                                     (sleep (random 0.1))
526                                                     (ignore-errors
527                                                      (terminate-thread thread)))
528                                                    (t
529                                                     (push thread safe)))
530                                              (setf x (not x))))))))
531         (signal-semaphore sem)
532         (setf ok t)
533         (join-thread interruptor)
534         (mapc #'join-thread safe)
535         (let ((k (count-if (lambda (th)
536                              (join-thread th :default nil))
537                            unsafe)))
538           (assert (= n (+ k (length safe))))
539           (assert unsafe))))))
540
541 (with-test (:name (:semaphore-notification :try-sempahore)
542             :skipped-on '(not :sb-thread))
543   (let* ((sem (make-semaphore))
544          (note (make-semaphore-notification)))
545     (try-semaphore sem 1 note)
546     (assert (not (semaphore-notification-status note)))
547     (signal-semaphore sem)
548     (try-semaphore sem 1 note)
549     (assert (semaphore-notification-status note))))