missing CAS-locks and barriers
[sbcl.git] / src / code / target-thread.lisp
1 ;;;; support for threads in the target machine
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 ;;; CAS Lock
15 ;;;
16 ;;; Locks don't come any simpler -- or more lightweight than this. While
17 ;;; this is probably a premature optimization for most users, we still
18 ;;; need it internally for implementing condition variables outside Futex
19 ;;; builds.
20
21 (defmacro with-cas-lock ((place) &body body)
22   #!+sb-doc
23   "Runs BODY with interrupts disabled and *CURRENT-THREAD* compare-and-swapped
24 into PLACE instead of NIL. PLACE must be a place acceptable to
25 COMPARE-AND-SWAP, and must initially hold NIL.
26
27 WITH-CAS-LOCK is suitable mostly when the critical section needing protection
28 is very small, and cost of allocating a separate lock object would be
29 prohibitive. While it is the most lightweight locking constructed offered by
30 SBCL, it is also the least scalable if the section is heavily contested or
31 long.
32
33 WITH-CAS-LOCK can be entered recursively."
34   `(without-interrupts
35      (%with-cas-lock (,place) ,@body)))
36
37 (defmacro %with-cas-lock ((place) &body body &environment env)
38   (with-unique-names (owner self)
39     (multiple-value-bind (vars vals old new cas-form read-form)
40         (sb!ext:get-cas-expansion place env)
41       `(let* (,@(mapcar #'list vars vals)
42               (,owner (progn
43                         (barrier (:read))
44                         ,read-form))
45               (,self *current-thread*)
46               (,old nil)
47               (,new ,self))
48          (unwind-protect
49               (progn
50                 (unless (eq ,owner ,self)
51                   (loop until (loop repeat 100
52                                     when (and (progn
53                                                 (barrier (:read))
54                                                 (not ,read-form))
55                                               (not (setf ,owner ,cas-form)))
56                                     return t
57                                     else
58                                     do (sb!ext:spin-loop-hint))
59                         do (thread-yield)))
60                 ,@body)
61            ;; FIXME: SETF + write barrier should to be enough here.
62            ;; ...but GET-CAS-EXPANSION doesn't return a WRITE-FORM.
63            ;; ...maybe it should?
64            (unless (eq ,owner ,self)
65              (let ((,old ,self)
66                    (,new nil))
67                (unless (eq ,old ,cas-form)
68                  (bug "Failed to release CAS lock!")))))))))
69
70 ;;; Conditions
71
72 (define-condition thread-error (error)
73   ((thread :reader thread-error-thread :initarg :thread))
74   #!+sb-doc
75   (:documentation
76    "Conditions of type THREAD-ERROR are signalled when thread operations fail.
77 The offending thread is initialized by the :THREAD initialization argument and
78 read by the function THREAD-ERROR-THREAD."))
79
80 (define-condition thread-deadlock (thread-error)
81   ((cycle :initarg :cycle :reader thread-deadlock-cycle))
82   (:report
83    (lambda (condition stream)
84      (let ((*print-circle* t))
85        (format stream "Deadlock cycle detected:~%~@<   ~@;~
86                      ~{~:@_~S~:@_~}~:@>"
87                (mapcar #'car (thread-deadlock-cycle condition)))))))
88
89 #!+sb-doc
90 (setf
91  (fdocumentation 'thread-error-thread 'function)
92  "Return the offending thread that the THREAD-ERROR pertains to.")
93
94 (define-condition symbol-value-in-thread-error (cell-error thread-error)
95   ((info :reader symbol-value-in-thread-error-info :initarg :info))
96   (:report
97    (lambda (condition stream)
98      (destructuring-bind (op problem)
99          (symbol-value-in-thread-error-info condition)
100        (format stream "Cannot ~(~A~) value of ~S in ~S: ~S"
101                op
102                (cell-error-name condition)
103                (thread-error-thread condition)
104                (ecase problem
105                  (:unbound-in-thread "the symbol is unbound in thread.")
106                  (:no-tls-value "the symbol has no thread-local value.")
107                  (:thread-dead "the thread has exited.")
108                  (:invalid-tls-value "the thread-local value is not valid."))))))
109   #!+sb-doc
110   (:documentation
111    "Signalled when SYMBOL-VALUE-IN-THREAD or its SETF version fails due to eg.
112 the symbol not having a thread-local value, or the target thread having
113 exited. The offending symbol can be accessed using CELL-ERROR-NAME, and the
114 offending thread using THREAD-ERROR-THREAD."))
115
116 (define-condition join-thread-error (thread-error)
117   ((problem :initarg :problem :reader join-thread-problem))
118   (:report (lambda (c s)
119              (ecase (join-thread-problem c)
120                (:abort
121                 (format s "Joining thread failed: thread ~A ~
122                            did not return normally."
123                         (thread-error-thread c)))
124                (:timeout
125                 (format s "Joining thread timed out: thread ~A ~
126                            did not exit in time."
127                         (thread-error-thread c))))))
128   #!+sb-doc
129   (:documentation
130    "Signalled when joining a thread fails due to abnormal exit of the thread
131 to be joined. The offending thread can be accessed using
132 THREAD-ERROR-THREAD."))
133
134 (define-deprecated-function :late "1.0.29.17" join-thread-error-thread thread-error-thread
135     (condition)
136   (thread-error-thread condition))
137
138 (define-condition interrupt-thread-error (thread-error) ()
139   (:report (lambda (c s)
140              (format s "Interrupt thread failed: thread ~A has exited."
141                      (thread-error-thread c))))
142   #!+sb-doc
143   (:documentation
144    "Signalled when interrupting a thread fails because the thread has already
145 exited. The offending thread can be accessed using THREAD-ERROR-THREAD."))
146
147 (define-deprecated-function :late "1.0.29.17" interrupt-thread-error-thread thread-error-thread
148     (condition)
149   (thread-error-thread condition))
150
151 ;;; Of the WITH-PINNED-OBJECTS in this file, not every single one is
152 ;;; necessary because threads are only supported with the conservative
153 ;;; gencgc and numbers on the stack (returned by GET-LISP-OBJ-ADDRESS)
154 ;;; are treated as references.
155
156 ;;; set the doc here because in early-thread FDOCUMENTATION is not
157 ;;; available, yet
158 #!+sb-doc
159 (setf (fdocumentation '*current-thread* 'variable)
160       "Bound in each thread to the thread itself.")
161
162 #!+sb-doc
163 (setf
164  (fdocumentation 'thread-name 'function)
165  "Name of the thread. Can be assigned to using SETF. Thread names can be
166 arbitrary printable objects, and need not be unique.")
167
168 (def!method print-object ((thread thread) stream)
169   (print-unreadable-object (thread stream :type t :identity t)
170     (let* ((cookie (list thread))
171            (info (if (thread-alive-p thread)
172                      :running
173                      (multiple-value-list
174                       (join-thread thread :default cookie))))
175            (state (if (eq :running info)
176                       (let* ((thing (progn
177                                       (barrier (:read))
178                                       (thread-waiting-for thread))))
179                         (typecase thing
180                           (cons
181                            (list "waiting on:" (cdr thing)
182                                  "timeout: " (car thing)))
183                           (null
184                            (list info))
185                           (t
186                            (list "waiting on:" thing))))
187                       (if (eq cookie (car info))
188                           (list :aborted)
189                           :finished)))
190            (values (when (eq :finished state)
191                      info))
192            (*print-level* 4))
193       (format stream
194               "~@[~S ~]~:[~{~I~A~^~2I~_ ~}~_~;~A~:[ no values~; values: ~:*~{~S~^, ~}~]~]"
195               (thread-name thread)
196               (eq :finished state)
197               state
198               values))))
199
200 (defun print-lock (lock name owner stream)
201   (let ((*print-circle* t))
202     (print-unreadable-object (lock stream :type t :identity (not name))
203       (if owner
204           (format stream "~@[~S ~]~2I~_owner: ~S" name owner)
205           (format stream "~@[~S ~](free)" name)))))
206
207 (def!method print-object ((mutex mutex) stream)
208   (print-lock mutex (mutex-name mutex) (mutex-owner mutex) stream))
209
210 (defun thread-alive-p (thread)
211   #!+sb-doc
212   "Return T if THREAD is still alive. Note that the return value is
213 potentially stale even before the function returns, as the thread may exit at
214 any time."
215   (thread-%alive-p thread))
216
217 ;; A thread is eligible for gc iff it has finished and there are no
218 ;; more references to it. This list is supposed to keep a reference to
219 ;; all running threads.
220 (defvar *all-threads* ())
221 (defvar *all-threads-lock* (make-mutex :name "all threads lock"))
222
223 (defvar *default-alloc-signal* nil)
224
225 (defmacro with-all-threads-lock (&body body)
226   `(with-system-mutex (*all-threads-lock*)
227      ,@body))
228
229 (defun list-all-threads ()
230   #!+sb-doc
231   "Return a list of the live threads. Note that the return value is
232 potentially stale even before the function returns, as new threads may be
233 created and old ones may exit at any time."
234   (with-all-threads-lock
235     (copy-list *all-threads*)))
236
237 (declaim (inline current-thread-sap))
238 (defun current-thread-sap ()
239   (sb!vm::current-thread-offset-sap sb!vm::thread-this-slot))
240
241 (declaim (inline current-thread-os-thread))
242 (defun current-thread-os-thread ()
243   #!+sb-thread
244   (sap-int (sb!vm::current-thread-offset-sap sb!vm::thread-os-thread-slot))
245   #!-sb-thread
246   0)
247
248 (defun init-initial-thread ()
249   (/show0 "Entering INIT-INITIAL-THREAD")
250   (let ((initial-thread (%make-thread :name "initial thread"
251                                       :%alive-p t
252                                       :os-thread (current-thread-os-thread))))
253     (setq *current-thread* initial-thread)
254     ;; Either *all-threads* is empty or it contains exactly one thread
255     ;; in case we are in reinit since saving core with multiple
256     ;; threads doesn't work.
257     (setq *all-threads* (list initial-thread))))
258 \f
259
260 ;;;; Aliens, low level stuff
261
262 (define-alien-routine "kill_safely"
263     integer
264   (os-thread #!-alpha unsigned-long #!+alpha unsigned-int)
265   (signal int))
266
267 #!+sb-thread
268 (progn
269   ;; FIXME it would be good to define what a thread id is or isn't
270   ;; (our current assumption is that it's a fixnum).  It so happens
271   ;; that on Linux it's a pid, but it might not be on posix thread
272   ;; implementations.
273   (define-alien-routine ("create_thread" %create-thread)
274       unsigned-long (lisp-fun-address unsigned-long))
275
276   (declaim (inline %block-deferrable-signals))
277   (define-alien-routine ("block_deferrable_signals" %block-deferrable-signals)
278       void
279     (where sb!alien:unsigned-long)
280     (old sb!alien:unsigned-long))
281
282   (defun block-deferrable-signals ()
283     (%block-deferrable-signals 0 0))
284
285   #!+sb-futex
286   (progn
287     (declaim (inline futex-wait %futex-wait futex-wake))
288
289     (define-alien-routine ("futex_wait" %futex-wait)
290         int (word unsigned-long) (old-value unsigned-long)
291         (to-sec long) (to-usec unsigned-long))
292
293     (defun futex-wait (word old to-sec to-usec)
294       (with-interrupts
295         (%futex-wait word old to-sec to-usec)))
296
297     (define-alien-routine "futex_wake"
298         int (word unsigned-long) (n unsigned-long))))
299
300 ;;; used by debug-int.lisp to access interrupt contexts
301 #!-(or sb-fluid sb-thread) (declaim (inline sb!vm::current-thread-offset-sap))
302 #!-sb-thread
303 (defun sb!vm::current-thread-offset-sap (n)
304   (declare (type (unsigned-byte 27) n))
305   (sap-ref-sap (alien-sap (extern-alien "all_threads" (* t)))
306                (* n sb!vm:n-word-bytes)))
307
308 #!+sb-thread
309 (defun sb!vm::current-thread-offset-sap (n)
310   (declare (type (unsigned-byte 27) n))
311   (sb!vm::current-thread-offset-sap n))
312 \f
313
314 (defmacro with-deadlocks ((thread lock &optional (timeout nil timeoutp)) &body forms)
315   (with-unique-names (n-thread n-lock new n-timeout)
316     `(let* ((,n-thread ,thread)
317             (,n-lock ,lock)
318             (,n-timeout ,(when timeoutp
319                            `(or ,timeout
320                                 (when sb!impl::*deadline*
321                                   sb!impl::*deadline-seconds*))))
322             (,new (if ,n-timeout
323                       ;; Using CONS tells the rest of the system there's a
324                       ;; timeout in place, so it isn't considered a deadlock.
325                       (cons ,n-timeout ,n-lock)
326                       ,n-lock)))
327        (declare (dynamic-extent ,new))
328        ;; No WITHOUT-INTERRUPTS, since WITH-DEADLOCKS is used
329        ;; in places where interrupts should already be disabled.
330        (unwind-protect
331             (progn
332               (setf (thread-waiting-for ,n-thread) ,new)
333               (barrier (:write))
334               ,@forms)
335          ;; Interrupt handlers and GC save and restore any
336          ;; previous wait marks using WITHOUT-DEADLOCKS below.
337          (setf (thread-waiting-for ,n-thread) nil)
338          (barrier (:write))))))
339 \f
340 ;;;; Mutexes
341
342 #!+sb-doc
343 (setf (fdocumentation 'make-mutex 'function)
344       "Create a mutex."
345       (fdocumentation 'mutex-name 'function)
346       "The name of the mutex. Setfable.")
347
348 #!+(and sb-thread sb-futex)
349 (progn
350   (define-structure-slot-addressor mutex-state-address
351       :structure mutex
352       :slot state)
353   ;; Important: current code assumes these are fixnums or other
354   ;; lisp objects that don't need pinning.
355   (defconstant +lock-free+ 0)
356   (defconstant +lock-taken+ 1)
357   (defconstant +lock-contested+ 2))
358
359 (defun mutex-owner (mutex)
360   "Current owner of the mutex, NIL if the mutex is free. Naturally,
361 this is racy by design (another thread may acquire the mutex after
362 this function returns), it is intended for informative purposes. For
363 testing whether the current thread is holding a mutex see
364 HOLDING-MUTEX-P."
365   ;; Make sure to get the current value.
366   (sb!ext:compare-and-swap (mutex-%owner mutex) nil nil))
367
368 ;;; Signals an error if owner of LOCK is waiting on a lock whose release
369 ;;; depends on the current thread. Does not detect deadlocks from sempahores.
370 (defun check-deadlock ()
371   (let* ((self *current-thread*)
372          (origin (progn
373                    (barrier (:read))
374                    (thread-waiting-for self))))
375     (labels ((detect-deadlock (lock)
376                (let ((other-thread (mutex-%owner lock)))
377                  (cond ((not other-thread))
378                        ((eq self other-thread)
379                         (let* ((chain (deadlock-chain self origin))
380                                (barf
381                                 (format nil
382                                         "~%WARNING: DEADLOCK CYCLE DETECTED:~%~@<   ~@;~
383                                          ~{~:@_~S~:@_~}~:@>~
384                                          ~%END OF CYCLE~%"
385                                         (mapcar #'car chain))))
386                           ;; Barf to stderr in case the system is too tied up
387                           ;; to report the error properly -- to avoid cross-talk
388                           ;; build the whole string up first.
389                           (write-string barf sb!sys:*stderr*)
390                           (finish-output sb!sys:*stderr*)
391                           (error 'thread-deadlock
392                                  :thread *current-thread*
393                                  :cycle chain)))
394                        (t
395                         (let ((other-lock (progn
396                                             (barrier (:read))
397                                             (thread-waiting-for other-thread))))
398                           ;; If the thread is waiting with a timeout OTHER-LOCK
399                           ;; is a cons, and we don't consider it a deadlock -- since
400                           ;; it will time out on its own sooner or later.
401                           (when (mutex-p other-lock)
402                             (detect-deadlock other-lock)))))))
403              (deadlock-chain (thread lock)
404                (let* ((other-thread (mutex-owner lock))
405                       (other-lock (when other-thread
406                                     (barrier (:read))
407                                     (thread-waiting-for other-thread))))
408                  (cond ((not other-thread)
409                         ;; The deadlock is gone -- maybe someone unwound
410                         ;; from the same deadlock already?
411                         (return-from check-deadlock nil))
412                        ((consp other-lock)
413                         ;; There's a timeout -- no deadlock.
414                         (return-from check-deadlock nil))
415                        ((waitqueue-p other-lock)
416                         ;; Not a lock.
417                         (return-from check-deadlock nil))
418                        ((eq self other-thread)
419                         ;; Done
420                         (list (list thread lock)))
421                        (t
422                         (if other-lock
423                             (cons (list thread lock)
424                                   (deadlock-chain other-thread other-lock))
425                             ;; Again, the deadlock is gone?
426                             (return-from check-deadlock nil)))))))
427       ;; Timeout means there is no deadlock
428       (when (mutex-p origin)
429         (detect-deadlock origin)
430         t))))
431
432 (defun %try-mutex (mutex new-owner)
433   (declare (type mutex mutex) (optimize (speed 3)))
434   (barrier (:read))
435   (let ((old (mutex-%owner mutex)))
436     (when (eq new-owner old)
437       (error "Recursive lock attempt ~S." mutex))
438     #!-sb-thread
439     (when old
440       (error "Strange deadlock on ~S in an unithreaded build?" mutex))
441     #!-sb-futex
442     (and (not old)
443          ;; Don't even bother to try to CAS if it looks bad.
444          (not (sb!ext:compare-and-swap (mutex-%owner mutex) nil new-owner)))
445     #!+sb-futex
446     ;; From the Mutex 2 algorithm from "Futexes are Tricky" by Ulrich Drepper.
447     (when (eql +lock-free+ (sb!ext:compare-and-swap (mutex-state mutex)
448                                                     +lock-free+
449                                                     +lock-taken+))
450       (let ((prev (sb!ext:compare-and-swap (mutex-%owner mutex) nil new-owner)))
451         (when prev
452           (bug "Old owner in free mutex: ~S" prev))
453         t))))
454
455 #!+sb-thread
456 (defun %%wait-for-mutex (mutex new-owner to-sec to-usec stop-sec stop-usec)
457   (declare (type mutex mutex) (optimize (speed 3)))
458   #!-sb-futex
459   (declare (ignore to-sec to-usec))
460   #!-sb-futex
461   (flet ((cas ()
462            (loop repeat 100
463                  when (and (progn
464                              (barrier (:read))
465                              (not (mutex-%owner mutex)))
466                            (not (sb!ext:compare-and-swap (mutex-%owner mutex) nil
467                                                          new-owner)))
468                  do (return-from cas t)
469                  else
470                  do
471                     (sb!ext:spin-loop-hint))
472            ;; Check for pending interrupts.
473            (with-interrupts nil)))
474     (declare (dynamic-extent #'cas))
475     (sb!impl::%%wait-for #'cas stop-sec stop-usec))
476   #!+sb-futex
477   ;; This is a fairly direct translation of the Mutex 2 algorithm from
478   ;; "Futexes are Tricky" by Ulrich Drepper.
479   (flet ((maybe (old)
480            (when (eql +lock-free+ old)
481              (let ((prev (sb!ext:compare-and-swap (mutex-%owner mutex)
482                                                   nil new-owner)))
483                (when prev
484                  (bug "Old owner in free mutex: ~S" prev))
485                (return-from %%wait-for-mutex t)))))
486     (prog ((old (sb!ext:compare-and-swap (mutex-state mutex)
487                                          +lock-free+ +lock-taken+)))
488        ;; Got it right off the bat?
489        (maybe old)
490      :retry
491        ;; Mark it as contested, and sleep. (Exception: it was just released.)
492        (when (or (eql +lock-contested+ old)
493                  (not (eql +lock-free+
494                            (sb!ext:compare-and-swap
495                             (mutex-state mutex) +lock-taken+ +lock-contested+))))
496          (when (eql 1 (with-pinned-objects (mutex)
497                         (futex-wait (mutex-state-address mutex)
498                                     (get-lisp-obj-address +lock-contested+)
499                                     (or to-sec -1)
500                                     (or to-usec 0))))
501            ;; -1 = EWOULDBLOCK, possibly spurious wakeup
502            ;;  0 = normal wakeup
503            ;;  1 = ETIMEDOUT ***DONE***
504            ;;  2 = EINTR, a spurious wakeup
505            (return-from %%wait-for-mutex nil)))
506        ;; Try to get it, still marking it as contested.
507        (maybe
508         (sb!ext:compare-and-swap (mutex-state mutex) +lock-free+ +lock-contested+))
509        ;; Update timeout if necessary.
510        (when stop-sec
511          (setf (values to-sec to-usec)
512                (sb!impl::relative-decoded-times stop-sec stop-usec)))
513        ;; Spin.
514        (go :retry))))
515
516 #!+sb-thread
517 (defun %wait-for-mutex (mutex self timeout to-sec to-usec stop-sec stop-usec deadlinep)
518   (with-deadlocks (self mutex timeout)
519     (with-interrupts (check-deadlock))
520     (tagbody
521      :again
522        (return-from %wait-for-mutex
523          (or (%%wait-for-mutex mutex self to-sec to-usec stop-sec stop-usec)
524              (when deadlinep
525                (signal-deadline)
526                ;; FIXME: substract elapsed time from timeout...
527                (setf (values to-sec to-usec stop-sec stop-usec deadlinep)
528                      (decode-timeout timeout))
529                (go :again)))))))
530
531 (defun get-mutex (mutex &optional new-owner (waitp t) (timeout nil))
532   #!+sb-doc
533   "Deprecated in favor of GRAB-MUTEX."
534   (declare (ignorable waitp timeout))
535   (let ((new-owner (or new-owner *current-thread*)))
536     (or (%try-mutex mutex new-owner)
537         #!+sb-thread
538         (when waitp
539           (multiple-value-call #'%wait-for-mutex
540             mutex new-owner timeout (decode-timeout timeout))))))
541
542 (defun grab-mutex (mutex &key (waitp t) (timeout nil))
543   #!+sb-doc
544   "Acquire MUTEX for the current thread. If WAITP is true (the default) and
545 the mutex is not immediately available, sleep until it is available.
546
547 If TIMEOUT is given, it specifies a relative timeout, in seconds, on how long
548 GRAB-MUTEX should try to acquire the lock in the contested case.
549
550 If GRAB-MUTEX returns T, the lock acquisition was successful. In case of WAITP
551 being NIL, or an expired TIMEOUT, GRAB-MUTEX may also return NIL which denotes
552 that GRAB-MUTEX did -not- acquire the lock.
553
554 Notes:
555
556   - GRAB-MUTEX is not interrupt safe. The correct way to call it is:
557
558       (WITHOUT-INTERRUPTS
559         ...
560         (ALLOW-WITH-INTERRUPTS (GRAB-MUTEX ...))
561         ...)
562
563     WITHOUT-INTERRUPTS is necessary to avoid an interrupt unwinding the call
564     while the mutex is in an inconsistent state while ALLOW-WITH-INTERRUPTS
565     allows the call to be interrupted from sleep.
566
567   - (GRAB-MUTEX <mutex> :timeout 0.0) differs from
568     (GRAB-MUTEX <mutex> :waitp nil) in that the former may signal a
569     DEADLINE-TIMEOUT if the global deadline was due already on entering
570     GRAB-MUTEX.
571
572     The exact interplay of GRAB-MUTEX and deadlines are reserved to change in
573     future versions.
574
575   - It is recommended that you use WITH-MUTEX instead of calling GRAB-MUTEX
576     directly.
577 "
578   (declare (ignorable waitp timeout))
579   (let ((self *current-thread*))
580     (or (%try-mutex mutex self)
581         #!+sb-thread
582         (when waitp
583           (multiple-value-call #'%wait-for-mutex
584             mutex self timeout (decode-timeout timeout))))))
585
586 (defun release-mutex (mutex &key (if-not-owner :punt))
587   #!+sb-doc
588   "Release MUTEX by setting it to NIL. Wake up threads waiting for
589 this mutex.
590
591 RELEASE-MUTEX is not interrupt safe: interrupts should be disabled
592 around calls to it.
593
594 If the current thread is not the owner of the mutex then it silently
595 returns without doing anything (if IF-NOT-OWNER is :PUNT), signals a
596 WARNING (if IF-NOT-OWNER is :WARN), or releases the mutex anyway (if
597 IF-NOT-OWNER is :FORCE)."
598   (declare (type mutex mutex))
599   ;; Order matters: set owner to NIL before releasing state.
600   (let* ((self *current-thread*)
601          (old-owner (sb!ext:compare-and-swap (mutex-%owner mutex) self nil)))
602     (unless (eq self old-owner)
603       (ecase if-not-owner
604         ((:punt) (return-from release-mutex nil))
605         ((:warn)
606          (warn "Releasing ~S, owned by another thread: ~S" mutex old-owner))
607         ((:force)))
608       (setf (mutex-%owner mutex) nil)
609       ;; FIXME: Is a :memory barrier too strong here?  Can we use a :write
610       ;; barrier instead?
611       (barrier (:memory)))
612     #!+sb-futex
613     (when old-owner
614       ;; FIXME: once ATOMIC-INCF supports struct slots with word sized
615       ;; unsigned-byte type this can be used:
616       ;;
617       ;;     (let ((old (sb!ext:atomic-incf (mutex-state mutex) -1)))
618       ;;       (unless (eql old +lock-free+)
619       ;;         (setf (mutex-state mutex) +lock-free+)
620       ;;         (with-pinned-objects (mutex)
621       ;;           (futex-wake (mutex-state-address mutex) 1))))
622       (let ((old (sb!ext:compare-and-swap (mutex-state mutex)
623                                           +lock-taken+ +lock-free+)))
624         (when (eql old +lock-contested+)
625           (sb!ext:compare-and-swap (mutex-state mutex)
626                                    +lock-contested+ +lock-free+)
627           (with-pinned-objects (mutex)
628             (futex-wake (mutex-state-address mutex) 1))))
629       nil)))
630 \f
631
632 ;;;; Waitqueues/condition variables
633
634 #!+(or (not sb-thread) sb-futex)
635 (defstruct (waitqueue (:constructor %make-waitqueue))
636   #!+sb-doc
637   "Waitqueue type."
638   (name nil :type (or null thread-name))
639   #!+sb-futex
640   (token nil))
641
642 #!+(and sb-thread (not sb-futex))
643 (progn
644   (defstruct (waitqueue (:constructor %make-waitqueue))
645     #!+sb-doc
646     "Waitqueue type."
647     (name nil :type (or null thread-name))
648     ;; For WITH-CAS-LOCK: because CONDITION-WAIT must be able to call
649     ;; %WAITQUEUE-WAKEUP without re-aquiring the mutex, we need a separate
650     ;; lock. In most cases this should be uncontested thanks to the mutex --
651     ;; the only case where that might not be true is when CONDITION-WAIT
652     ;; unwinds and %WAITQUEUE-DROP is called.
653     %owner
654     %head
655     %tail)
656
657   (defun %waitqueue-enqueue (thread queue)
658     (setf (thread-waiting-for thread) queue)
659     (let ((head (waitqueue-%head queue))
660           (tail (waitqueue-%tail queue))
661           (new (list thread)))
662       (unless head
663         (setf (waitqueue-%head queue) new))
664       (when tail
665         (setf (cdr tail) new))
666       (setf (waitqueue-%tail queue) new)
667       nil))
668   (defun %waitqueue-drop (thread queue)
669     (setf (thread-waiting-for thread) nil)
670     (let ((head (waitqueue-%head queue)))
671       (do ((list head (cdr list))
672            (prev nil))
673           ((eq (car list) thread)
674            (let ((rest (cdr list)))
675              (cond (prev
676                     (setf (cdr prev) rest))
677                    (t
678                     (setf (waitqueue-%head queue) rest
679                           prev rest)))
680              (unless rest
681                (setf (waitqueue-%tail queue) prev))))
682         (setf prev list)))
683     nil)
684   (defun %waitqueue-wakeup (queue n)
685     (declare (fixnum n))
686     (loop while (plusp n)
687           for next = (let ((head (waitqueue-%head queue))
688                            (tail (waitqueue-%tail queue)))
689                        (when head
690                          (if (eq head tail)
691                              (setf (waitqueue-%head queue) nil
692                                    (waitqueue-%tail queue) nil)
693                              (setf (waitqueue-%head queue) (cdr head)))
694                          (car head)))
695           while next
696           do (when (eq queue (sb!ext:compare-and-swap
697                               (thread-waiting-for next) queue nil))
698                (decf n)))
699     nil))
700
701 (def!method print-object ((waitqueue waitqueue) stream)
702   (print-unreadable-object (waitqueue stream :type t :identity t)
703     (format stream "~@[~A~]" (waitqueue-name waitqueue))))
704
705 (defun make-waitqueue (&key name)
706   #!+sb-doc
707   "Create a waitqueue."
708   (%make-waitqueue :name name))
709
710 #!+sb-doc
711 (setf (fdocumentation 'waitqueue-name 'function)
712       "The name of the waitqueue. Setfable.")
713
714 #!+(and sb-thread sb-futex)
715 (define-structure-slot-addressor waitqueue-token-address
716     :structure waitqueue
717     :slot token)
718
719 (defun condition-wait (queue mutex &key timeout)
720   #!+sb-doc
721   "Atomically release MUTEX and start waiting on QUEUE for till another thread
722 wakes us up using either CONDITION-NOTIFY or CONDITION-BROADCAST on that
723 queue, at which point we re-acquire MUTEX and return T.
724
725 Spurious wakeups are possible.
726
727 If TIMEOUT is given, it is the maximum number of seconds to wait, including
728 both waiting for the wakeup and the time to re-acquire MUTEX. Unless both
729 wakeup and re-acquisition do not occur within the given time, returns NIL
730 without re-acquiring the mutex.
731
732 If CONDITION-WAIT unwinds, it may do so with or without the mutex being held.
733
734 Important: Since CONDITION-WAIT may return without CONDITION-NOTIFY having
735 occurred the correct way to write code that uses CONDITION-WAIT is to loop
736 around the call, checking the the associated data:
737
738   (defvar *data* nil)
739   (defvar *queue* (make-waitqueue))
740   (defvar *lock* (make-mutex))
741
742   ;; Consumer
743   (defun pop-data (&optional timeout)
744     (with-mutex (*lock*)
745       (loop until *data*
746             do (or (condition-wait *queue* *lock* :timeout timeout)
747                    ;; Lock not held, must unwind without touching *data*.
748                    (return-from pop-data nil)))
749       (pop *data*)))
750
751   ;; Producer
752   (defun push-data (data)
753     (with-mutex (*lock*)
754       (push data *data*)
755       (condition-notify *queue*)))
756 "
757   #!-sb-thread
758   (declare (ignore queue))
759   (assert mutex)
760   #!-sb-thread
761   (sb!ext:wait-for nil :timeout timeout) ; Yeah...
762   #!+sb-thread
763   (let ((me *current-thread*))
764     (barrier (:read))
765     (assert (eq me (mutex-%owner mutex)))
766     (multiple-value-bind (to-sec to-usec stop-sec stop-usec deadlinep)
767         (decode-timeout timeout)
768       (let ((status :interrupted))
769         ;; Need to disable interrupts so that we don't miss grabbing the
770         ;; mutex on our way out.
771         (without-interrupts
772           (unwind-protect
773                (progn
774                  #!-sb-futex
775                  (progn
776                    (%with-cas-lock ((waitqueue-%owner queue))
777                      (%waitqueue-enqueue me queue))
778                    (release-mutex mutex)
779                    (setf status
780                          (or (flet ((wakeup ()
781                                       (barrier (:read))
782                                       (when (neq queue
783                                                  (thread-waiting-for me))
784                                         :ok)))
785                                (declare (dynamic-extent #'wakeup))
786                                (allow-with-interrupts
787                                  (sb!impl::%%wait-for #'wakeup stop-sec stop-usec)))
788                              :timeout)))
789                  #!+sb-futex
790                  (with-pinned-objects (queue me)
791                    (setf (waitqueue-token queue) me)
792                    (release-mutex mutex)
793                    ;; Now we go to sleep using futex-wait. If anyone else
794                    ;; manages to grab MUTEX and call CONDITION-NOTIFY during
795                    ;; this comment, it will change the token, and so futex-wait
796                    ;; returns immediately instead of sleeping. Ergo, no lost
797                    ;; wakeup. We may get spurious wakeups, but that's ok.
798                    (setf status
799                          (case (allow-with-interrupts
800                                  (futex-wait (waitqueue-token-address queue)
801                                              (get-lisp-obj-address me)
802                                              ;; our way of saying "no
803                                              ;; timeout":
804                                              (or to-sec -1)
805                                              (or to-usec 0)))
806                            ((1)
807                             ;;  1 = ETIMEDOUT
808                             :timeout)
809                            (t
810                             ;; -1 = EWOULDBLOCK, possibly spurious wakeup
811                             ;;  0 = normal wakeup
812                             ;;  2 = EINTR, a spurious wakeup
813                             :ok)))))
814             #!-sb-futex
815             (%with-cas-lock ((waitqueue-%owner queue))
816               (if (eq queue (thread-waiting-for me))
817                   (%waitqueue-drop me queue)
818                   (unless (eq :ok status)
819                     ;; CONDITION-NOTIFY thinks we've been woken up, but really
820                     ;; we're unwinding. Wake someone else up.
821                     (%waitqueue-wakeup queue 1))))
822             ;; Update timeout for mutex re-aquisition.
823             (when (and (eq :ok status) to-sec)
824               (setf (values to-sec to-usec)
825                     (sb!impl::relative-decoded-times stop-sec stop-usec)))
826             ;; If we ran into deadline, try to get the mutex before
827             ;; signaling. If we don't unwind it will look like a normal
828             ;; return from user perspective.
829             (when (and (eq :timeout status) deadlinep)
830               (let ((got-it (%try-mutex mutex me)))
831                 (allow-with-interrupts
832                   (signal-deadline)
833                   (cond (got-it
834                          (return-from condition-wait t))
835                         (t
836                          ;; The deadline may have changed.
837                          (setf (values to-sec to-usec stop-sec stop-usec deadlinep)
838                                (decode-timeout timeout))
839                          (setf status :ok))))))
840             ;; Re-acquire the mutex for normal return.
841             (when (eq :ok status)
842               (unless (or (%try-mutex mutex me)
843                           (allow-with-interrupts
844                             (%wait-for-mutex mutex me timeout
845                                              to-sec to-usec
846                                              stop-sec stop-usec deadlinep)))
847                 (setf status :timeout)))))
848         (or (eq :ok status)
849             (unless (eq :timeout status)
850               ;; The only case we return normally without re-acquiring the
851               ;; mutex is when there is a :TIMEOUT that runs out.
852               (bug "CONDITION-WAIT: invalid status on normal return: ~S" status)))))))
853
854 (defun condition-notify (queue &optional (n 1))
855   #!+sb-doc
856   "Notify N threads waiting on QUEUE.
857
858 IMPORTANT: The same mutex that is used in the corresponding CONDITION-WAIT
859 must be held by this thread during this call."
860   #!-sb-thread
861   (declare (ignore queue n))
862   #!-sb-thread
863   (error "Not supported in unithread builds.")
864   #!+sb-thread
865   (declare (type (and fixnum (integer 1)) n))
866   (/show0 "Entering CONDITION-NOTIFY")
867   #!+sb-thread
868   (progn
869     #!-sb-futex
870     (with-cas-lock ((waitqueue-%owner queue))
871       (%waitqueue-wakeup queue n))
872     #!+sb-futex
873     (progn
874     ;; No problem if >1 thread notifies during the comment in condition-wait:
875     ;; as long as the value in queue-data isn't the waiting thread's id, it
876     ;; matters not what it is -- using the queue object itself is handy.
877     ;;
878     ;; XXX we should do something to ensure that the result of this setf
879     ;; is visible to all CPUs.
880     ;;
881     ;; ^-- surely futex_wake() involves a memory barrier?
882       (setf (waitqueue-token queue) queue)
883       (with-pinned-objects (queue)
884         (futex-wake (waitqueue-token-address queue) n)))))
885
886 (defun condition-broadcast (queue)
887   #!+sb-doc
888   "Notify all threads waiting on QUEUE.
889
890 IMPORTANT: The same mutex that is used in the corresponding CONDITION-WAIT
891 must be held by this thread during this call."
892   (condition-notify queue
893                     ;; On a 64-bit platform truncating M-P-F to an int
894                     ;; results in -1, which wakes up only one thread.
895                     (ldb (byte 29 0)
896                          most-positive-fixnum)))
897 \f
898
899 ;;;; Semaphores
900
901 (defstruct (semaphore (:constructor %make-semaphore (name %count)))
902   #!+sb-doc
903   "Semaphore type. The fact that a SEMAPHORE is a STRUCTURE-OBJECT
904 should be considered an implementation detail, and may change in the
905 future."
906   (name    nil :type (or null thread-name))
907   (%count    0 :type (integer 0))
908   (waitcount 0 :type sb!vm:word)
909   (mutex (make-mutex))
910   (queue (make-waitqueue)))
911
912 (setf (fdocumentation 'semaphore-name 'function)
913       "The name of the semaphore INSTANCE. Setfable.")
914
915 (declaim (inline semaphore-count))
916 (defun semaphore-count (instance)
917   "Returns the current count of the semaphore INSTANCE."
918   (barrier (:read))
919   (semaphore-%count instance))
920
921 (defun make-semaphore (&key name (count 0))
922   #!+sb-doc
923   "Create a semaphore with the supplied COUNT and NAME."
924   (%make-semaphore name count))
925
926 (defun wait-on-semaphore (semaphore &key timeout)
927   #!+sb-doc
928   "Decrement the count of SEMAPHORE if the count would not be negative. Else
929 blocks until the semaphore can be decremented. Returns T on success.
930
931 If TIMEOUT is given, it is the maximum number of seconds to wait. If the count
932 cannot be decremented in that time, returns NIL without decrementing the
933 count."
934   ;; A more direct implementation based directly on futexes should be
935   ;; possible.
936   ;;
937   ;; We need to disable interrupts so that we don't forget to
938   ;; decrement the waitcount (which would happen if an asynch
939   ;; interrupt should catch us on our way out from the loop.)
940   ;;
941   ;; FIXME: No timeout on initial mutex acquisition.
942   (with-system-mutex ((semaphore-mutex semaphore) :allow-with-interrupts t)
943     ;; Quick check: is it positive? If not, enter the wait loop.
944     (let ((count (semaphore-%count semaphore)))
945       (if (plusp count)
946           (setf (semaphore-%count semaphore) (1- count))
947           (unwind-protect
948                (progn
949                  ;; Need to use ATOMIC-INCF despite the lock, because on our
950                  ;; way out from here we might not be locked anymore -- so
951                  ;; another thread might be tweaking this in parallel using
952                  ;; ATOMIC-DECF. No danger over overflow, since there it
953                  ;; at most one increment per thread waiting on the semaphore.
954                  (sb!ext:atomic-incf (semaphore-waitcount semaphore))
955                  (loop until (plusp (setf count (semaphore-%count semaphore)))
956                        do (or (condition-wait (semaphore-queue semaphore)
957                                               (semaphore-mutex semaphore)
958                                               :timeout timeout)
959                               (return-from wait-on-semaphore nil)))
960                  (setf (semaphore-%count semaphore) (1- count)))
961             ;; Need to use ATOMIC-DECF instead of DECF, as CONDITION-WAIT
962             ;; may unwind without the lock being held due to timeouts.
963             (sb!ext:atomic-decf (semaphore-waitcount semaphore))))))
964   t)
965
966 (defun try-semaphore (semaphore &optional (n 1))
967   #!+sb-doc
968   "Try to decrement the count of SEMAPHORE by N. If the count were to
969 become negative, punt and return NIL, otherwise return true."
970   (declare (type (integer 1) n))
971   (with-system-mutex ((semaphore-mutex semaphore) :allow-with-interrupts t)
972     (let ((new-count (- (semaphore-%count semaphore) n)))
973       (when (not (minusp new-count))
974         (setf (semaphore-%count semaphore) new-count)))))
975
976 (defun signal-semaphore (semaphore &optional (n 1))
977   #!+sb-doc
978   "Increment the count of SEMAPHORE by N. If there are threads waiting
979 on this semaphore, then N of them is woken up."
980   (declare (type (integer 1) n))
981   ;; Need to disable interrupts so that we don't lose a wakeup after
982   ;; we have incremented the count.
983   (with-system-mutex ((semaphore-mutex semaphore) :allow-with-interrupts t)
984     (let ((waitcount (semaphore-waitcount semaphore))
985           (count (incf (semaphore-%count semaphore) n)))
986       (when (plusp waitcount)
987         (condition-notify (semaphore-queue semaphore) (min waitcount count))))))
988 \f
989
990 ;;;; Job control, independent listeners
991
992 (defstruct session
993   (lock (make-mutex :name "session lock"))
994   (threads nil)
995   (interactive-threads nil)
996   (interactive-threads-queue (make-waitqueue)))
997
998 (defvar *session* nil)
999
1000 ;;; The debugger itself tries to acquire the session lock, don't let
1001 ;;; funny situations (like getting a sigint while holding the session
1002 ;;; lock) occur. At the same time we need to allow interrupts while
1003 ;;; *waiting* for the session lock for things like GET-FOREGROUND to
1004 ;;; be interruptible.
1005 ;;;
1006 ;;; Take care: we sometimes need to obtain the session lock while
1007 ;;; holding on to *ALL-THREADS-LOCK*, so we must _never_ obtain it
1008 ;;; _after_ getting a session lock! (Deadlock risk.)
1009 ;;;
1010 ;;; FIXME: It would be good to have ordered locks to ensure invariants
1011 ;;; like the above.
1012 (defmacro with-session-lock ((session) &body body)
1013   `(with-system-mutex ((session-lock ,session) :allow-with-interrupts t)
1014      ,@body))
1015
1016 (defun new-session ()
1017   (make-session :threads (list *current-thread*)
1018                 :interactive-threads (list *current-thread*)))
1019
1020 (defun init-job-control ()
1021   (/show0 "Entering INIT-JOB-CONTROL")
1022   (setf *session* (new-session))
1023   (/show0 "Exiting INIT-JOB-CONTROL"))
1024
1025 (defun %delete-thread-from-session (thread session)
1026   (with-session-lock (session)
1027     (setf (session-threads session)
1028           (delete thread (session-threads session))
1029           (session-interactive-threads session)
1030           (delete thread (session-interactive-threads session)))))
1031
1032 (defun call-with-new-session (fn)
1033   (%delete-thread-from-session *current-thread* *session*)
1034   (let ((*session* (new-session)))
1035     (funcall fn)))
1036
1037 (defmacro with-new-session (args &body forms)
1038   (declare (ignore args))               ;for extensibility
1039   (sb!int:with-unique-names (fb-name)
1040     `(labels ((,fb-name () ,@forms))
1041       (call-with-new-session (function ,fb-name)))))
1042
1043 ;;; Remove thread from its session, if it has one.
1044 #!+sb-thread
1045 (defun handle-thread-exit (thread)
1046   (/show0 "HANDLING THREAD EXIT")
1047   ;; Lisp-side cleanup
1048   (with-all-threads-lock
1049     (setf (thread-%alive-p thread) nil)
1050     (setf (thread-os-thread thread) nil)
1051     (setq *all-threads* (delete thread *all-threads*))
1052     (when *session*
1053       (%delete-thread-from-session thread *session*))))
1054
1055 (defun terminate-session ()
1056   #!+sb-doc
1057   "Kill all threads in session except for this one.  Does nothing if current
1058 thread is not the foreground thread."
1059   ;; FIXME: threads created in other threads may escape termination
1060   (let ((to-kill
1061          (with-session-lock (*session*)
1062            (and (eq *current-thread*
1063                     (car (session-interactive-threads *session*)))
1064                 (session-threads *session*)))))
1065     ;; do the kill after dropping the mutex; unwind forms in dying
1066     ;; threads may want to do session things
1067     (dolist (thread to-kill)
1068       (unless (eq thread *current-thread*)
1069         ;; terminate the thread but don't be surprised if it has
1070         ;; exited in the meantime
1071         (handler-case (terminate-thread thread)
1072           (interrupt-thread-error ()))))))
1073
1074 ;;; called from top of invoke-debugger
1075 (defun debugger-wait-until-foreground-thread (stream)
1076   "Returns T if thread had been running in background, NIL if it was
1077 interactive."
1078   (declare (ignore stream))
1079   #!-sb-thread nil
1080   #!+sb-thread
1081   (prog1
1082       (with-session-lock (*session*)
1083         (not (member *current-thread*
1084                      (session-interactive-threads *session*))))
1085     (get-foreground)))
1086
1087 (defun get-foreground ()
1088   #!-sb-thread t
1089   #!+sb-thread
1090   (let ((was-foreground t))
1091     (loop
1092      (/show0 "Looping in GET-FOREGROUND")
1093      (with-session-lock (*session*)
1094        (let ((int-t (session-interactive-threads *session*)))
1095          (when (eq (car int-t) *current-thread*)
1096            (unless was-foreground
1097              (format *query-io* "Resuming thread ~A~%" *current-thread*))
1098            (return-from get-foreground t))
1099          (setf was-foreground nil)
1100          (unless (member *current-thread* int-t)
1101            (setf (cdr (last int-t))
1102                  (list *current-thread*)))
1103          (condition-wait
1104           (session-interactive-threads-queue *session*)
1105           (session-lock *session*)))))))
1106
1107 (defun release-foreground (&optional next)
1108   #!+sb-doc
1109   "Background this thread.  If NEXT is supplied, arrange for it to
1110 have the foreground next."
1111   #!-sb-thread (declare (ignore next))
1112   #!-sb-thread nil
1113   #!+sb-thread
1114   (with-session-lock (*session*)
1115     (when (rest (session-interactive-threads *session*))
1116       (setf (session-interactive-threads *session*)
1117             (delete *current-thread* (session-interactive-threads *session*))))
1118     (when next
1119       (setf (session-interactive-threads *session*)
1120             (list* next
1121                    (delete next (session-interactive-threads *session*)))))
1122     (condition-broadcast (session-interactive-threads-queue *session*))))
1123
1124 (defun foreground-thread ()
1125   (car (session-interactive-threads *session*)))
1126
1127 (defun make-listener-thread (tty-name)
1128   (assert (probe-file tty-name))
1129   (let* ((in (sb!unix:unix-open (namestring tty-name) sb!unix:o_rdwr #o666))
1130          (out (sb!unix:unix-dup in))
1131          (err (sb!unix:unix-dup in)))
1132     (labels ((thread-repl ()
1133                (sb!unix::unix-setsid)
1134                (let* ((sb!impl::*stdin*
1135                        (make-fd-stream in :input t :buffering :line
1136                                        :dual-channel-p t))
1137                       (sb!impl::*stdout*
1138                        (make-fd-stream out :output t :buffering :line
1139                                               :dual-channel-p t))
1140                       (sb!impl::*stderr*
1141                        (make-fd-stream err :output t :buffering :line
1142                                               :dual-channel-p t))
1143                       (sb!impl::*tty*
1144                        (make-fd-stream err :input t :output t
1145                                               :buffering :line
1146                                               :dual-channel-p t))
1147                       (sb!impl::*descriptor-handlers* nil))
1148                  (with-new-session ()
1149                    (unwind-protect
1150                         (sb!impl::toplevel-repl nil)
1151                      (sb!int:flush-standard-output-streams))))))
1152       (make-thread #'thread-repl))))
1153 \f
1154
1155 ;;;; The beef
1156
1157 (defun make-thread (function &key name arguments)
1158   #!+sb-doc
1159   "Create a new thread of NAME that runs FUNCTION with the argument
1160 list designator provided (defaults to no argument). When the function
1161 returns the thread exits. The return values of FUNCTION are kept
1162 around and can be retrieved by JOIN-THREAD."
1163   #!-sb-thread (declare (ignore function name arguments))
1164   #!-sb-thread (error "Not supported in unithread builds.")
1165   #!+sb-thread (assert (or (atom arguments)
1166                            (null (cdr (last arguments))))
1167                        (arguments)
1168                        "Argument passed to ~S, ~S, is an improper list."
1169                        'make-thread arguments)
1170   #!+sb-thread
1171   (let* ((thread (%make-thread :name name))
1172          (setup-sem (make-semaphore :name "Thread setup semaphore"))
1173          (real-function (coerce function 'function))
1174          (arguments     (if (listp arguments)
1175                             arguments
1176                             (list arguments)))
1177          (initial-function
1178           (named-lambda initial-thread-function ()
1179             ;; In time we'll move some of the binding presently done in C
1180             ;; here too.
1181             ;;
1182             ;; KLUDGE: Here we have a magic list of variables that are
1183             ;; not thread-safe for one reason or another.  As people
1184             ;; report problems with the thread safety of certain
1185             ;; variables, (e.g. "*print-case* in multiple threads
1186             ;; broken", sbcl-devel 2006-07-14), we add a few more
1187             ;; bindings here.  The Right Thing is probably some variant
1188             ;; of Allegro's *cl-default-special-bindings*, as that is at
1189             ;; least accessible to users to secure their own libraries.
1190             ;;   --njf, 2006-07-15
1191             ;;
1192             ;; As it is, this lambda must not cons until we are ready
1193             ;; to run GC. Be very careful.
1194             (let* ((*current-thread* thread)
1195                    (*restart-clusters* nil)
1196                    (*handler-clusters* (sb!kernel::initial-handler-clusters))
1197                    (*condition-restarts* nil)
1198                    (sb!impl::*deadline* nil)
1199                    (sb!impl::*deadline-seconds* nil)
1200                    (sb!impl::*step-out* nil)
1201                    ;; internal printer variables
1202                    (sb!impl::*previous-case* nil)
1203                    (sb!impl::*previous-readtable-case* nil)
1204                    (sb!impl::*internal-symbol-output-fun* nil)
1205                    (sb!impl::*descriptor-handlers* nil)) ; serve-event
1206               ;; Binding from C
1207               (setf sb!vm:*alloc-signal* *default-alloc-signal*)
1208               (setf (thread-os-thread thread) (current-thread-os-thread))
1209               (with-mutex ((thread-result-lock thread))
1210                 (with-all-threads-lock
1211                   (push thread *all-threads*))
1212                 (with-session-lock (*session*)
1213                   (push thread (session-threads *session*)))
1214                 (setf (thread-%alive-p thread) t)
1215                 (signal-semaphore setup-sem)
1216                 ;; can't use handling-end-of-the-world, because that flushes
1217                 ;; output streams, and we don't necessarily have any (or we
1218                 ;; could be sharing them)
1219                 (catch 'sb!impl::toplevel-catcher
1220                   (catch 'sb!impl::%end-of-the-world
1221                     (with-simple-restart
1222                         (terminate-thread
1223                          (format nil
1224                                  "~~@<Terminate this thread (~A)~~@:>"
1225                                  *current-thread*))
1226                       (without-interrupts
1227                         (unwind-protect
1228                              (with-local-interrupts
1229                                ;; Now that most things have a chance
1230                                ;; to work properly without messing up
1231                                ;; other threads, it's time to enable
1232                                ;; signals.
1233                                (sb!unix::unblock-deferrable-signals)
1234                                (setf (thread-result thread)
1235                                      (cons t
1236                                            (multiple-value-list
1237                                             (apply real-function arguments))))
1238                                ;; Try to block deferrables. An
1239                                ;; interrupt may unwind it, but for a
1240                                ;; normal exit it prevents interrupt
1241                                ;; loss.
1242                                (block-deferrable-signals))
1243                           ;; We're going down, can't handle interrupts
1244                           ;; sanely anymore. GC remains enabled.
1245                           (block-deferrable-signals)
1246                           ;; We don't want to run interrupts in a dead
1247                           ;; thread when we leave WITHOUT-INTERRUPTS.
1248                           ;; This potentially causes important
1249                           ;; interupts to be lost: SIGINT comes to
1250                           ;; mind.
1251                           (setq *interrupt-pending* nil)
1252                           (handle-thread-exit thread))))))))
1253             (values))))
1254     ;; If the starting thread is stopped for gc before it signals the
1255     ;; semaphore then we'd be stuck.
1256     (assert (not *gc-inhibit*))
1257     ;; Keep INITIAL-FUNCTION pinned until the child thread is
1258     ;; initialized properly. Wrap the whole thing in
1259     ;; WITHOUT-INTERRUPTS because we pass INITIAL-FUNCTION to another
1260     ;; thread.
1261     (without-interrupts
1262       (with-pinned-objects (initial-function)
1263         (let ((os-thread
1264                (%create-thread
1265                 (get-lisp-obj-address initial-function))))
1266           (when (zerop os-thread)
1267             (error "Can't create a new thread"))
1268           (wait-on-semaphore setup-sem)
1269           thread)))))
1270
1271 (defun join-thread (thread &key (default nil defaultp) timeout)
1272   #!+sb-doc
1273   "Suspend current thread until THREAD exits. Return the result values of the
1274 thread function.
1275
1276 If the thread does not exit normally within TIMEOUT seconds return DEFAULT if
1277 given, or else signal JOIN-THREAD-ERROR.
1278
1279 NOTE: Return convention in case of a timeout is exprimental and subject to
1280 change."
1281   (let ((lock (thread-result-lock thread))
1282         (got-it nil)
1283         (problem :timeout))
1284     (without-interrupts
1285       (unwind-protect
1286            (if (setf got-it
1287                      (allow-with-interrupts
1288                        ;; Don't use the timeout if the thread is not alive anymore.
1289                        (grab-mutex lock :timeout (and (thread-alive-p thread) timeout))))
1290                (cond ((car (thread-result thread))
1291                       (return-from join-thread
1292                         (values-list (cdr (thread-result thread)))))
1293                      (defaultp
1294                       (return-from join-thread default))
1295                      (t
1296                       (setf problem :abort)))
1297                (when defaultp
1298                  (return-from join-thread default)))
1299         (when got-it
1300           (release-mutex lock))))
1301     (error 'join-thread-error :thread thread :problem problem)))
1302
1303 (defun destroy-thread (thread)
1304   #!+sb-doc
1305   "Deprecated. Same as TERMINATE-THREAD."
1306   (terminate-thread thread))
1307
1308 (defmacro with-interruptions-lock ((thread) &body body)
1309   `(with-system-mutex ((thread-interruptions-lock ,thread))
1310      ,@body))
1311
1312 ;;; Called from the signal handler.
1313 #!-win32
1314 (defun run-interruption ()
1315   (let ((interruption (with-interruptions-lock (*current-thread*)
1316                         (pop (thread-interruptions *current-thread*)))))
1317     ;; If there is more to do, then resignal and let the normal
1318     ;; interrupt deferral mechanism take care of the rest. From the
1319     ;; OS's point of view the signal we are in the handler for is no
1320     ;; longer pending, so the signal will not be lost.
1321     (when (thread-interruptions *current-thread*)
1322       (kill-safely (thread-os-thread *current-thread*) sb!unix:sigpipe))
1323     (when interruption
1324       (funcall interruption))))
1325
1326 (defun interrupt-thread (thread function)
1327   #!+sb-doc
1328   "Interrupt the live THREAD and make it run FUNCTION. A moderate
1329 degree of care is expected for use of INTERRUPT-THREAD, due to its
1330 nature: if you interrupt a thread that was holding important locks
1331 then do something that turns out to need those locks, you probably
1332 won't like the effect. FUNCTION runs with interrupts disabled, but
1333 WITH-INTERRUPTS is allowed in it. Keep in mind that many things may
1334 enable interrupts (GET-MUTEX when contended, for instance) so the
1335 first thing to do is usually a WITH-INTERRUPTS or a
1336 WITHOUT-INTERRUPTS. Within a thread interrupts are queued, they are
1337 run in same the order they were sent."
1338   #!+win32
1339   (declare (ignore thread))
1340   #!+win32
1341   (with-interrupt-bindings
1342     (with-interrupts (funcall function)))
1343   #!-win32
1344   (let ((os-thread (thread-os-thread thread)))
1345     (cond ((not os-thread)
1346            (error 'interrupt-thread-error :thread thread))
1347           (t
1348            (with-interruptions-lock (thread)
1349              ;; Append to the end of the interruptions queue. It's
1350              ;; O(N), but it does not hurt to slow interruptors down a
1351              ;; bit when the queue gets long.
1352              (setf (thread-interruptions thread)
1353                    (append (thread-interruptions thread)
1354                            (list (lambda ()
1355                                    (without-interrupts
1356                                      (allow-with-interrupts
1357                                        (funcall function))))))))
1358            (when (minusp (kill-safely os-thread sb!unix:sigpipe))
1359              (error 'interrupt-thread-error :thread thread))))))
1360
1361 (defun terminate-thread (thread)
1362   #!+sb-doc
1363   "Terminate the thread identified by THREAD, by causing it to run
1364 SB-EXT:QUIT - the usual cleanup forms will be evaluated"
1365   (interrupt-thread thread 'sb!ext:quit))
1366
1367 (define-alien-routine "thread_yield" int)
1368
1369 #!+sb-doc
1370 (setf (fdocumentation 'thread-yield 'function)
1371       "Yield the processor to other threads.")
1372
1373 ;;; internal use only.  If you think you need to use these, either you
1374 ;;; are an SBCL developer, are doing something that you should discuss
1375 ;;; with an SBCL developer first, or are doing something that you
1376 ;;; should probably discuss with a professional psychiatrist first
1377 #!+sb-thread
1378 (progn
1379   (defun %thread-sap (thread)
1380     (let ((thread-sap (alien-sap (extern-alien "all_threads" (* t))))
1381           (target (thread-os-thread thread)))
1382       (loop
1383         (when (sap= thread-sap (int-sap 0)) (return nil))
1384         (let ((os-thread (sap-ref-word thread-sap
1385                                        (* sb!vm:n-word-bytes
1386                                           sb!vm::thread-os-thread-slot))))
1387           (when (= os-thread target) (return thread-sap))
1388           (setf thread-sap
1389                 (sap-ref-sap thread-sap (* sb!vm:n-word-bytes
1390                                            sb!vm::thread-next-slot)))))))
1391
1392   (defun %symbol-value-in-thread (symbol thread)
1393     ;; Prevent the thread from dying completely while we look for the TLS
1394     ;; area...
1395     (with-all-threads-lock
1396       (loop
1397         (if (thread-alive-p thread)
1398             (let* ((epoch sb!kernel::*gc-epoch*)
1399                    (offset (sb!kernel:get-lisp-obj-address
1400                             (sb!vm::symbol-tls-index symbol)))
1401                    (tl-val (sap-ref-word (%thread-sap thread) offset)))
1402               (cond ((zerop offset)
1403                      (return (values nil :no-tls-value)))
1404                     ((or (eql tl-val sb!vm:no-tls-value-marker-widetag)
1405                          (eql tl-val sb!vm:unbound-marker-widetag))
1406                      (return (values nil :unbound-in-thread)))
1407                     (t
1408                      (multiple-value-bind (obj ok) (make-lisp-obj tl-val nil)
1409                        ;; The value we constructed may be invalid if a GC has
1410                        ;; occurred. That is harmless, though, since OBJ is
1411                        ;; either in a register or on stack, and we are
1412                        ;; conservative on both on GENCGC -- so a bogus object
1413                        ;; is safe here as long as we don't return it. If we
1414                        ;; ever port threads to a non-conservative GC we must
1415                        ;; pin the TL-VAL address before constructing OBJ, or
1416                        ;; make WITH-ALL-THREADS-LOCK imply WITHOUT-GCING.
1417                        ;;
1418                        ;; The reason we don't just rely on TL-VAL pinning the
1419                        ;; object is that the call to MAKE-LISP-OBJ may cause
1420                        ;; bignum allocation, at which point TL-VAL might not
1421                        ;; be alive anymore -- hence the epoch check.
1422                        (when (eq epoch sb!kernel::*gc-epoch*)
1423                          (if ok
1424                              (return (values obj :ok))
1425                              (return (values obj :invalid-tls-value))))))))
1426             (return (values nil :thread-dead))))))
1427
1428   (defun %set-symbol-value-in-thread (symbol thread value)
1429     (with-pinned-objects (value)
1430       ;; Prevent the thread from dying completely while we look for the TLS
1431       ;; area...
1432       (with-all-threads-lock
1433         (if (thread-alive-p thread)
1434             (let ((offset (sb!kernel:get-lisp-obj-address
1435                            (sb!vm::symbol-tls-index symbol))))
1436               (cond ((zerop offset)
1437                      (values nil :no-tls-value))
1438                     (t
1439                      (setf (sap-ref-word (%thread-sap thread) offset)
1440                            (get-lisp-obj-address value))
1441                      (values value :ok))))
1442             (values nil :thread-dead)))))
1443
1444   (define-alien-variable tls-index-start unsigned-int)
1445
1446   ;; Get values from the TLS area of the current thread.
1447   (defun %thread-local-references ()
1448     (without-gcing
1449       (let ((sap (%thread-sap *current-thread*)))
1450         (loop for index from tls-index-start
1451                 below (symbol-value 'sb!vm::*free-tls-index*)
1452               for value = (sap-ref-word sap (* sb!vm:n-word-bytes index))
1453               for (obj ok) = (multiple-value-list (sb!kernel:make-lisp-obj value nil))
1454               unless (or (not ok)
1455                          (typep obj '(or fixnum character))
1456                          (member value
1457                                  '(#.sb!vm:no-tls-value-marker-widetag
1458                                    #.sb!vm:unbound-marker-widetag))
1459                          (member obj seen :test #'eq))
1460                 collect obj into seen
1461               finally (return seen))))))
1462
1463 (defun symbol-value-in-thread (symbol thread &optional (errorp t))
1464   "Return the local value of SYMBOL in THREAD, and a secondary value of T
1465 on success.
1466
1467 If the value cannot be retrieved (because the thread has exited or because it
1468 has no local binding for NAME) and ERRORP is true signals an error of type
1469 SYMBOL-VALUE-IN-THREAD-ERROR; if ERRORP is false returns a primary value of
1470 NIL, and a secondary value of NIL.
1471
1472 Can also be used with SETF to change the thread-local value of SYMBOL.
1473
1474 SYMBOL-VALUE-IN-THREAD is primarily intended as a debugging tool, and not as a
1475 mechanism for inter-thread communication."
1476   (declare (symbol symbol) (thread thread))
1477   #!+sb-thread
1478   (multiple-value-bind (res status) (%symbol-value-in-thread symbol thread)
1479     (if (eq :ok status)
1480         (values res t)
1481         (if errorp
1482             (error 'symbol-value-in-thread-error
1483                    :name symbol
1484                    :thread thread
1485                    :info (list :read status))
1486             (values nil nil))))
1487   #!-sb-thread
1488   (if (boundp symbol)
1489       (values (symbol-value symbol) t)
1490       (if errorp
1491           (error 'symbol-value-in-thread-error
1492                  :name symbol
1493                  :thread thread
1494                  :info (list :read :unbound-in-thread))
1495           (values nil nil))))
1496
1497 (defun (setf symbol-value-in-thread) (value symbol thread &optional (errorp t))
1498   (declare (symbol symbol) (thread thread))
1499   #!+sb-thread
1500   (multiple-value-bind (res status) (%set-symbol-value-in-thread symbol thread value)
1501     (if (eq :ok status)
1502         (values res t)
1503         (if errorp
1504             (error 'symbol-value-in-thread-error
1505                    :name symbol
1506                    :thread thread
1507                    :info (list :write status))
1508             (values nil nil))))
1509   #!-sb-thread
1510   (if (boundp symbol)
1511       (values (setf (symbol-value symbol) value) t)
1512       (if errorp
1513           (error 'symbol-value-in-thread-error
1514                  :name symbol
1515                  :thread thread
1516                  :info (list :write :unbound-in-thread))
1517           (values nil nil))))
1518
1519 (defun sb!vm::locked-symbol-global-value-add (symbol-name delta)
1520   (sb!vm::locked-symbol-global-value-add symbol-name delta))
1521 \f
1522
1523 ;;;; Stepping
1524
1525 (defun thread-stepping ()
1526   (make-lisp-obj
1527    (sap-ref-word (current-thread-sap)
1528                  (* sb!vm::thread-stepping-slot sb!vm:n-word-bytes))))
1529
1530 (defun (setf thread-stepping) (value)
1531   (setf (sap-ref-word (current-thread-sap)
1532                       (* sb!vm::thread-stepping-slot sb!vm:n-word-bytes))
1533         (get-lisp-obj-address value)))