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