5dfb84e6eb6c0feaf5aac3d3b23193c84e0c2c5f
[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 (not sb-lutex) sb-thread)
40   (state    0 :type fixnum)
41   #!+(and sb-lutex sb-thread)
42   (lutex (make-lutex)))
43
44 (defun mutex-value (mutex)
45   "Current owner of the mutex, NIL if the mutex is free. May return a
46 stale value, use MUTEX-OWNER instead."
47   (mutex-%owner mutex))
48
49 (defun holding-mutex-p (mutex)
50   "Test whether the current thread is holding MUTEX."
51   ;; This is about the only use for which a stale value of owner is
52   ;; sufficient.
53   (eq sb!thread:*current-thread* (mutex-%owner mutex)))
54
55 (defsetf mutex-value set-mutex-value)
56
57 (declaim (inline set-mutex-value))
58 (defun set-mutex-value (mutex value)
59   (declare (ignore mutex value))
60   (error "~S is no longer supported." '(setf mutex-value)))
61
62 (define-compiler-macro set-mutex-value (&whole form mutex value)
63   (declare (ignore mutex value))
64   (warn "~S is no longer supported, and will signal an error at runtime."
65         '(setf mutex-value))
66   form)
67
68 (def!struct spinlock
69   #!+sb-doc
70   "Spinlock type."
71   (name  nil :type (or null thread-name))
72   (value nil))
73
74 (sb!xc:defmacro without-thread-waiting-for ((&key already-without-interrupts) &body body)
75   (with-unique-names (thread prev)
76     (let ((without (if already-without-interrupts
77                        'progn
78                        'without-interrupts))
79           (with (if already-without-interrupts
80                     'progn
81                     'with-local-interrupts)))
82       `(let* ((,thread *current-thread*)
83               (,prev (thread-waiting-for ,thread)))
84          (flet ((exec () ,@body))
85            (if ,prev
86                (,without
87                 (unwind-protect
88                      (progn
89                        (setf (thread-waiting-for ,thread) nil)
90                        (,with (exec)))
91                   (setf (thread-waiting-for ,thread) ,prev)))
92                (exec)))))))
93
94 (sb!xc:defmacro with-mutex ((mutex &key (value '*current-thread*) (wait-p t))
95                             &body body)
96   #!+sb-doc
97   "Acquire MUTEX for the dynamic scope of BODY, setting it to VALUE or
98 some suitable default value if NIL.  If WAIT-P is non-NIL and the mutex
99 is in use, sleep until it is available"
100   `(dx-flet ((with-mutex-thunk () ,@body))
101      (call-with-mutex
102       #'with-mutex-thunk
103       ,mutex
104       ,value
105       ,wait-p)))
106
107 (sb!xc:defmacro with-system-mutex ((mutex
108                                     &key without-gcing allow-with-interrupts)
109                                    &body body)
110   `(dx-flet ((with-system-mutex-thunk () ,@body))
111      (,(cond (without-gcing
112                'call-with-system-mutex/without-gcing)
113              (allow-with-interrupts
114               'call-with-system-mutex/allow-with-interrupts)
115              (t
116               'call-with-system-mutex))
117        #'with-system-mutex-thunk
118        ,mutex)))
119
120 (sb!xc:defmacro with-system-spinlock ((spinlock &key) &body body)
121   `(dx-flet ((with-system-spinlock-thunk () ,@body))
122      (call-with-system-spinlock
123        #'with-system-spinlock-thunk
124        ,spinlock)))
125
126 (sb!xc:defmacro with-recursive-lock ((mutex) &body body)
127   #!+sb-doc
128   "Acquires MUTEX for the dynamic scope of BODY. Within that scope
129 further recursive lock attempts for the same mutex succeed. It is
130 allowed to mix WITH-MUTEX and WITH-RECURSIVE-LOCK for the same mutex
131 provided the default value is used for the mutex."
132   `(dx-flet ((with-recursive-lock-thunk () ,@body))
133      (call-with-recursive-lock
134       #'with-recursive-lock-thunk
135       ,mutex)))
136
137 (sb!xc:defmacro with-recursive-spinlock ((spinlock) &body body)
138   `(dx-flet ((with-recursive-spinlock-thunk () ,@body))
139      (call-with-recursive-spinlock
140       #'with-recursive-spinlock-thunk
141       ,spinlock)))
142
143 (sb!xc:defmacro with-recursive-system-spinlock ((spinlock
144                                                  &key without-gcing)
145                                                 &body body)
146   `(dx-flet ((with-recursive-system-spinlock-thunk () ,@body))
147      (,(cond (without-gcing
148                'call-with-recursive-system-spinlock/without-gcing)
149              (t
150               'call-with-recursive-system-spinlock))
151        #'with-recursive-system-spinlock-thunk
152        ,spinlock)))
153
154 (sb!xc:defmacro with-spinlock ((spinlock) &body body)
155   `(dx-flet ((with-spinlock-thunk () ,@body))
156      (call-with-spinlock
157       #'with-spinlock-thunk
158       ,spinlock)))
159
160 (macrolet ((def (name &optional variant)
161              `(defun ,(if variant (symbolicate name "/" variant) name)
162                   (function mutex)
163                 (declare (function function))
164                 (flet ((%call-with-system-mutex ()
165                          (dx-let (got-it)
166                            (unwind-protect
167                                 (when (setf got-it (get-mutex mutex))
168                                   (funcall function))
169                              (when got-it
170                                (release-mutex mutex))))))
171                   (declare (inline %call-with-system-mutex))
172                   ,(ecase variant
173                      (:without-gcing
174                        `(without-gcing (%call-with-system-mutex)))
175                      (:allow-with-interrupts
176                        `(without-interrupts
177                           (allow-with-interrupts (%call-with-system-mutex))))
178                      ((nil)
179                       `(without-interrupts (%call-with-system-mutex))))))))
180   (def call-with-system-mutex)
181   (def call-with-system-mutex :without-gcing)
182   (def call-with-system-mutex :allow-with-interrupts))
183
184 #!-sb-thread
185 (progn
186   (macrolet ((def (name &optional variant)
187                `(defun ,(if variant (symbolicate name "/" variant) name)
188                     (function lock)
189                   (declare (ignore lock) (function function))
190                   ,(ecase variant
191                     (:without-gcing
192                       `(without-gcing (funcall function)))
193                     (:allow-with-interrupts
194                       `(without-interrupts
195                          (allow-with-interrupts (funcall function))))
196                     ((nil)
197                       `(without-interrupts (funcall function)))))))
198     (def call-with-system-spinlock)
199     (def call-with-recursive-system-spinlock)
200     (def call-with-recursive-system-spinlock :without-gcing))
201
202   (defun call-with-mutex (function mutex value waitp)
203     (declare (ignore mutex value waitp)
204              (function function))
205     (funcall function))
206
207   (defun call-with-recursive-lock (function mutex)
208     (declare (ignore mutex) (function function))
209     (funcall function))
210
211   (defun call-with-spinlock (function spinlock)
212     (declare (ignore spinlock) (function function))
213     (funcall function))
214
215   (defun call-with-recursive-spinlock (function spinlock)
216     (declare (ignore spinlock) (function function))
217     (funcall function)))
218
219 #!+sb-thread
220 ;;; KLUDGE: These need to use DX-LET, because the cleanup form that
221 ;;; closes over GOT-IT causes a value-cell to be allocated for it --
222 ;;; and we prefer that to go on the stack since it can.
223 (progn
224   (defun call-with-system-spinlock (function spinlock)
225     (declare (function function))
226     (without-interrupts
227       (dx-let (got-it)
228         (unwind-protect
229              (when (setf got-it (get-spinlock spinlock))
230                (funcall function))
231           (when got-it
232             (release-spinlock spinlock))))))
233
234   (macrolet ((def (name &optional variant)
235                `(defun ,(if variant (symbolicate name "/" variant) name)
236                     (function spinlock)
237                   (declare (function function))
238                   (flet ((%call-with-system-spinlock ()
239                            (dx-let ((inner-lock-p
240                                      (eq *current-thread*
241                                          (spinlock-value spinlock)))
242                                     (got-it nil))
243                              (unwind-protect
244                                   (when (or inner-lock-p
245                                             (setf got-it
246                                                   (get-spinlock spinlock)))
247                                     (funcall function))
248                                (when got-it
249                                  (release-spinlock spinlock))))))
250                     (declare (inline %call-with-system-spinlock))
251                     ,(ecase variant
252                       (:without-gcing
253                         `(without-gcing (%call-with-system-spinlock)))
254                       ((nil)
255                         `(without-interrupts (%call-with-system-spinlock))))))))
256     (def call-with-recursive-system-spinlock)
257     (def call-with-recursive-system-spinlock :without-gcing))
258
259   (defun call-with-spinlock (function spinlock)
260     (declare (function function))
261     (dx-let ((got-it nil))
262       (without-interrupts
263         (unwind-protect
264              (when (setf got-it (allow-with-interrupts
265                                  (get-spinlock spinlock)))
266                (with-local-interrupts (funcall function)))
267           (when got-it
268             (release-spinlock spinlock))))))
269
270   (defun call-with-mutex (function mutex value waitp)
271     (declare (function function))
272     (dx-let ((got-it nil))
273       (without-interrupts
274         (unwind-protect
275              (when (setq got-it (allow-with-interrupts
276                                  (get-mutex mutex value waitp)))
277                (with-local-interrupts (funcall function)))
278           (when got-it
279             (release-mutex mutex))))))
280
281   (defun call-with-recursive-lock (function mutex)
282     (declare (function function))
283     (dx-let ((inner-lock-p (eq (mutex-%owner mutex) *current-thread*))
284              (got-it nil))
285       (without-interrupts
286         (unwind-protect
287              (when (or inner-lock-p (setf got-it (allow-with-interrupts
288                                                   (get-mutex mutex))))
289                (with-local-interrupts (funcall function)))
290           (when got-it
291             (release-mutex mutex))))))
292
293   (defun call-with-recursive-spinlock (function spinlock)
294     (declare (function function))
295     (dx-let ((inner-lock-p (eq (spinlock-value spinlock) *current-thread*))
296           (got-it nil))
297       (without-interrupts
298         (unwind-protect
299              (when (or inner-lock-p (setf got-it (allow-with-interrupts
300                                                   (get-spinlock spinlock))))
301                (with-local-interrupts (funcall function)))
302           (when got-it
303             (release-spinlock spinlock)))))))