killing lutexes, adding timeouts
[sbcl.git] / src / code / thread.lisp
1 ;;;; support for threads needed at cross-compile time
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; This software is derived from the CMU CL system, which was
7 ;;;; written at Carnegie Mellon University and released into the
8 ;;;; public domain. The software is in the public domain and is
9 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
10 ;;;; files for more information.
11
12 (in-package "SB!THREAD")
13
14 (def!type thread-name ()
15   'simple-string)
16
17 (def!struct (thread (:constructor %make-thread))
18   #!+sb-doc
19   "Thread type. Do not rely on threads being structs as it may change
20 in future versions."
21   (name          nil :type (or thread-name null))
22   (%alive-p      nil :type boolean)
23   (os-thread     nil :type (or integer null))
24   (interruptions nil :type list)
25   (result        nil :type list)
26   (interruptions-lock
27    (make-mutex :name "thread interruptions lock")
28    :type mutex)
29   (result-lock
30    (make-mutex :name "thread result lock")
31    :type mutex)
32   waiting-for)
33
34 (def!struct mutex
35   #!+sb-doc
36   "Mutex type."
37   (name   nil :type (or null thread-name))
38   (%owner nil :type (or null thread))
39   #!+(and sb-thread sb-futex)
40   (state    0 :type fixnum))
41
42 (defun mutex-value (mutex)
43   "Current owner of the mutex, NIL if the mutex is free. May return a
44 stale value, use MUTEX-OWNER instead."
45   (mutex-%owner mutex))
46
47 (defun holding-mutex-p (mutex)
48   "Test whether the current thread is holding MUTEX."
49   ;; This is about the only use for which a stale value of owner is
50   ;; sufficient.
51   (eq sb!thread:*current-thread* (mutex-%owner mutex)))
52
53 (defsetf mutex-value set-mutex-value)
54
55 (declaim (inline set-mutex-value))
56 (defun set-mutex-value (mutex value)
57   (declare (ignore mutex value))
58   (error "~S is no longer supported." '(setf mutex-value)))
59
60 (define-compiler-macro set-mutex-value (&whole form mutex value)
61   (declare (ignore mutex value))
62   (warn "~S is no longer supported, and will signal an error at runtime."
63         '(setf mutex-value))
64   form)
65
66 (def!struct spinlock
67   #!+sb-doc
68   "Spinlock type."
69   (name  nil :type (or null thread-name))
70   (value nil))
71
72 (sb!xc:defmacro without-thread-waiting-for ((&key already-without-interrupts) &body body)
73   (with-unique-names (thread prev)
74     (let ((without (if already-without-interrupts
75                        'progn
76                        'without-interrupts))
77           (with (if already-without-interrupts
78                     'progn
79                     'with-local-interrupts)))
80       `(let* ((,thread *current-thread*)
81               (,prev (thread-waiting-for ,thread)))
82          (flet ((exec () ,@body))
83            (if ,prev
84                (,without
85                 (unwind-protect
86                      (progn
87                        (setf (thread-waiting-for ,thread) nil)
88                        (,with (exec)))
89                   (setf (thread-waiting-for ,thread) ,prev)))
90                (exec)))))))
91
92 (sb!xc:defmacro with-mutex ((mutex &key (value '*current-thread*) (wait-p t))
93                             &body body)
94   #!+sb-doc
95   "Acquire MUTEX for the dynamic scope of BODY, setting it to VALUE or
96 some suitable default value if NIL.  If WAIT-P is non-NIL and the mutex
97 is in use, sleep until it is available"
98   `(dx-flet ((with-mutex-thunk () ,@body))
99      (call-with-mutex
100       #'with-mutex-thunk
101       ,mutex
102       ,value
103       ,wait-p)))
104
105 (sb!xc:defmacro with-system-mutex ((mutex
106                                     &key without-gcing allow-with-interrupts)
107                                    &body body)
108   `(dx-flet ((with-system-mutex-thunk () ,@body))
109      (,(cond (without-gcing
110                'call-with-system-mutex/without-gcing)
111              (allow-with-interrupts
112               'call-with-system-mutex/allow-with-interrupts)
113              (t
114               'call-with-system-mutex))
115        #'with-system-mutex-thunk
116        ,mutex)))
117
118 (sb!xc:defmacro with-system-spinlock ((spinlock &key) &body body)
119   `(dx-flet ((with-system-spinlock-thunk () ,@body))
120      (call-with-system-spinlock
121        #'with-system-spinlock-thunk
122        ,spinlock)))
123
124 (sb!xc:defmacro with-recursive-lock ((mutex) &body body)
125   #!+sb-doc
126   "Acquires MUTEX for the dynamic scope of BODY. Within that scope
127 further recursive lock attempts for the same mutex succeed. It is
128 allowed to mix WITH-MUTEX and WITH-RECURSIVE-LOCK for the same mutex
129 provided the default value is used for the mutex."
130   `(dx-flet ((with-recursive-lock-thunk () ,@body))
131      (call-with-recursive-lock
132       #'with-recursive-lock-thunk
133       ,mutex)))
134
135 (sb!xc:defmacro with-recursive-spinlock ((spinlock) &body body)
136   `(dx-flet ((with-recursive-spinlock-thunk () ,@body))
137      (call-with-recursive-spinlock
138       #'with-recursive-spinlock-thunk
139       ,spinlock)))
140
141 (sb!xc:defmacro with-recursive-system-spinlock ((spinlock
142                                                  &key without-gcing)
143                                                 &body body)
144   `(dx-flet ((with-recursive-system-spinlock-thunk () ,@body))
145      (,(cond (without-gcing
146                'call-with-recursive-system-spinlock/without-gcing)
147              (t
148               'call-with-recursive-system-spinlock))
149        #'with-recursive-system-spinlock-thunk
150        ,spinlock)))
151
152 (sb!xc:defmacro with-spinlock ((spinlock) &body body)
153   `(dx-flet ((with-spinlock-thunk () ,@body))
154      (call-with-spinlock
155       #'with-spinlock-thunk
156       ,spinlock)))
157
158 (macrolet ((def (name &optional variant)
159              `(defun ,(if variant (symbolicate name "/" variant) name)
160                   (function mutex)
161                 (declare (function function))
162                 (flet ((%call-with-system-mutex ()
163                          (dx-let (got-it)
164                            (unwind-protect
165                                 (when (setf got-it (get-mutex mutex))
166                                   (funcall function))
167                              (when got-it
168                                (release-mutex mutex))))))
169                   (declare (inline %call-with-system-mutex))
170                   ,(ecase variant
171                      (:without-gcing
172                        `(without-gcing (%call-with-system-mutex)))
173                      (:allow-with-interrupts
174                        `(without-interrupts
175                           (allow-with-interrupts (%call-with-system-mutex))))
176                      ((nil)
177                       `(without-interrupts (%call-with-system-mutex))))))))
178   (def call-with-system-mutex)
179   (def call-with-system-mutex :without-gcing)
180   (def call-with-system-mutex :allow-with-interrupts))
181
182 #!-sb-thread
183 (progn
184   (macrolet ((def (name &optional variant)
185                `(defun ,(if variant (symbolicate name "/" variant) name)
186                     (function lock)
187                   (declare (ignore lock) (function function))
188                   ,(ecase variant
189                     (:without-gcing
190                       `(without-gcing (funcall function)))
191                     (:allow-with-interrupts
192                       `(without-interrupts
193                          (allow-with-interrupts (funcall function))))
194                     ((nil)
195                       `(without-interrupts (funcall function)))))))
196     (def call-with-system-spinlock)
197     (def call-with-recursive-system-spinlock)
198     (def call-with-recursive-system-spinlock :without-gcing))
199
200   (defun call-with-mutex (function mutex value waitp)
201     (declare (ignore mutex value waitp)
202              (function function))
203     (funcall function))
204
205   (defun call-with-recursive-lock (function mutex)
206     (declare (ignore mutex) (function function))
207     (funcall function))
208
209   (defun call-with-spinlock (function spinlock)
210     (declare (ignore spinlock) (function function))
211     (funcall function))
212
213   (defun call-with-recursive-spinlock (function spinlock)
214     (declare (ignore spinlock) (function function))
215     (funcall function)))
216
217 #!+sb-thread
218 ;;; KLUDGE: These need to use DX-LET, because the cleanup form that
219 ;;; closes over GOT-IT causes a value-cell to be allocated for it --
220 ;;; and we prefer that to go on the stack since it can.
221 (progn
222   (defun call-with-system-spinlock (function spinlock)
223     (declare (function function))
224     (without-interrupts
225       (dx-let (got-it)
226         (unwind-protect
227              (when (setf got-it (get-spinlock spinlock))
228                (funcall function))
229           (when got-it
230             (release-spinlock spinlock))))))
231
232   (macrolet ((def (name &optional variant)
233                `(defun ,(if variant (symbolicate name "/" variant) name)
234                     (function spinlock)
235                   (declare (function function))
236                   (flet ((%call-with-system-spinlock ()
237                            (dx-let ((inner-lock-p
238                                      (eq *current-thread*
239                                          (spinlock-value spinlock)))
240                                     (got-it nil))
241                              (unwind-protect
242                                   (when (or inner-lock-p
243                                             (setf got-it
244                                                   (get-spinlock spinlock)))
245                                     (funcall function))
246                                (when got-it
247                                  (release-spinlock spinlock))))))
248                     (declare (inline %call-with-system-spinlock))
249                     ,(ecase variant
250                       (:without-gcing
251                         `(without-gcing (%call-with-system-spinlock)))
252                       ((nil)
253                         `(without-interrupts (%call-with-system-spinlock))))))))
254     (def call-with-recursive-system-spinlock)
255     (def call-with-recursive-system-spinlock :without-gcing))
256
257   (defun call-with-spinlock (function spinlock)
258     (declare (function function))
259     (dx-let ((got-it nil))
260       (without-interrupts
261         (unwind-protect
262              (when (setf got-it (allow-with-interrupts
263                                  (get-spinlock spinlock)))
264                (with-local-interrupts (funcall function)))
265           (when got-it
266             (release-spinlock spinlock))))))
267
268   (defun call-with-mutex (function mutex value waitp)
269     (declare (function function))
270     (dx-let ((got-it nil))
271       (without-interrupts
272         (unwind-protect
273              (when (setq got-it (allow-with-interrupts
274                                  (get-mutex mutex value waitp)))
275                (with-local-interrupts (funcall function)))
276           (when got-it
277             (release-mutex mutex))))))
278
279   (defun call-with-recursive-lock (function mutex)
280     (declare (function function))
281     (dx-let ((inner-lock-p (eq (mutex-%owner mutex) *current-thread*))
282              (got-it nil))
283       (without-interrupts
284         (unwind-protect
285              (when (or inner-lock-p (setf got-it (allow-with-interrupts
286                                                   (get-mutex mutex))))
287                (with-local-interrupts (funcall function)))
288           (when got-it
289             (release-mutex mutex))))))
290
291   (defun call-with-recursive-spinlock (function spinlock)
292     (declare (function function))
293     (dx-let ((inner-lock-p (eq (spinlock-value spinlock) *current-thread*))
294           (got-it nil))
295       (without-interrupts
296         (unwind-protect
297              (when (or inner-lock-p (setf got-it (allow-with-interrupts
298                                                   (get-spinlock spinlock))))
299                (with-local-interrupts (funcall function)))
300           (when got-it
301             (release-spinlock spinlock)))))))