42e0530da8cc75d224e9be30eec5c7964e1e37b4
[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 ;;; Of the WITH-PINNED-OBJECTS in this file, not every single one is
15 ;;; necessary because threads are only supported with the conservative
16 ;;; gencgc and numbers on the stack (returned by GET-LISP-OBJ-ADDRESS)
17 ;;; are treated as references. In fact, I think there isn't one that's
18 ;;; truly important as of now.
19
20 ;;; set the doc here because in early-thread FDOCUMENTATION is not
21 ;;; available, yet
22 #!+sb-doc
23 (setf (sb!kernel:fdocumentation '*current-thread* 'variable)
24       "Bound in each thread to the thread itself.")
25
26 (defstruct (thread (:constructor %make-thread))
27   #!+sb-doc
28   "Thread type. Do not rely on threads being structs as it may change
29 in future versions."
30   name
31   %alive-p
32   os-thread
33   interruptions
34   (interruptions-lock (make-mutex :name "thread interruptions lock")))
35
36 #!+sb-doc
37 (setf (sb!kernel:fdocumentation 'thread-name 'function)
38       "The name of the thread. Setfable.")
39
40 (def!method print-object ((thread thread) stream)
41   (if (thread-name thread)
42       (print-unreadable-object (thread stream :type t :identity t)
43         (prin1 (thread-name thread) stream))
44       (print-unreadable-object (thread stream :type t :identity t)
45         ;; body is empty => there is only one space between type and
46         ;; identity
47         ))
48   thread)
49
50 (defun thread-alive-p (thread)
51   #!+sb-doc
52   "Check if THREAD is running."
53   (thread-%alive-p thread))
54
55 ;; A thread is eligible for gc iff it has finished and there are no
56 ;; more references to it. This list is supposed to keep a reference to
57 ;; all running threads.
58 (defvar *all-threads* ())
59 (defvar *all-threads-lock* (make-mutex :name "all threads lock"))
60
61 (defun list-all-threads ()
62   #!+sb-doc
63   "Return a list of the live threads."
64   (with-mutex (*all-threads-lock*)
65     (copy-list *all-threads*)))
66
67 (declaim (inline current-thread-sap))
68 (defun current-thread-sap ()
69   (sb!vm::current-thread-offset-sap sb!vm::thread-this-slot))
70
71 (declaim (inline current-thread-sap-id))
72 (defun current-thread-sap-id ()
73   (sap-int
74    (sb!vm::current-thread-offset-sap sb!vm::thread-os-thread-slot)))
75
76 (defun init-initial-thread ()
77   (let ((initial-thread (%make-thread :name "initial thread"
78                                       :%alive-p t
79                                       :os-thread (current-thread-sap-id))))
80     (setq *current-thread* initial-thread)
81     ;; Either *all-threads* is empty or it contains exactly one thread
82     ;; in case we are in reinit since saving core with multiple
83     ;; threads doesn't work.
84     (setq *all-threads* (list initial-thread))))
85
86 ;;;;
87
88 #!+sb-thread
89 (progn
90   ;; FIXME it would be good to define what a thread id is or isn't
91   ;; (our current assumption is that it's a fixnum).  It so happens
92   ;; that on Linux it's a pid, but it might not be on posix thread
93   ;; implementations.
94   (define-alien-routine ("create_thread" %create-thread)
95       unsigned-long (lisp-fun-address unsigned-long))
96
97   (define-alien-routine "signal_interrupt_thread"
98       integer (os-thread unsigned-long))
99
100   (define-alien-routine "block_blockable_signals"
101       void)
102
103   (declaim (inline futex-wait futex-wake))
104
105   (sb!alien:define-alien-routine "futex_wait"
106       int (word unsigned-long) (old-value unsigned-long))
107
108   (sb!alien:define-alien-routine "futex_wake"
109       int (word unsigned-long) (n unsigned-long)))
110
111 ;;; used by debug-int.lisp to access interrupt contexts
112 #!-(and sb-fluid sb-thread) (declaim (inline sb!vm::current-thread-offset-sap))
113 #!-sb-thread
114 (defun sb!vm::current-thread-offset-sap (n)
115   (declare (type (unsigned-byte 27) n))
116   (sap-ref-sap (alien-sap (extern-alien "all_threads" (* t)))
117                (* n sb!vm:n-word-bytes)))
118
119 ;;;; spinlocks
120
121 (defstruct spinlock
122   #!+sb-doc
123   "Spinlock type."
124   (name nil :type (or null simple-string))
125   (value 0))
126
127 (declaim (inline get-spinlock release-spinlock))
128
129 ;;; The bare 2 here and below are offsets of the slots in the struct.
130 ;;; There ought to be some better way to get these numbers
131 (defun get-spinlock (spinlock new-value)
132   (declare (optimize (speed 3) (safety 0))
133            #!-sb-thread
134            (ignore spinlock new-value))
135   ;; %instance-set-conditional can test for 0 (which is a fixnum) and
136   ;; store any value
137   #!+sb-thread
138   (loop until
139         (eql (sb!vm::%instance-set-conditional spinlock 2 0 new-value) 0)))
140
141 (defun release-spinlock (spinlock)
142   (declare (optimize (speed 3) (safety 0))
143            #!-sb-thread (ignore spinlock))
144   ;; %instance-set-conditional cannot compare arbitrary objects
145   ;; meaningfully, so
146   ;; (sb!vm::%instance-set-conditional spinlock 2 our-value 0)
147   ;; does not work for bignum thread ids.
148   #!+sb-thread
149   (sb!vm::%instance-set spinlock 2 0))
150
151 (defmacro with-spinlock ((spinlock) &body body)
152   (sb!int:with-unique-names (lock)
153     `(let ((,lock ,spinlock))
154       (get-spinlock ,lock *current-thread*)
155       (unwind-protect
156            (progn ,@body)
157         (release-spinlock ,lock)))))
158
159 ;;;; mutexes
160
161 (defstruct mutex
162   #!+sb-doc
163   "Mutex type."
164   (name nil :type (or null simple-string))
165   (value nil))
166
167 #!+sb-doc
168 (setf (sb!kernel:fdocumentation 'make-mutex 'function)
169       "Create a mutex."
170       (sb!kernel:fdocumentation 'mutex-name 'function)
171       "The name of the mutex. Setfable."
172       (sb!kernel:fdocumentation 'mutex-value 'function)
173       "The value of the mutex. NIL if the mutex is free. Setfable.")
174
175 #!+sb-thread
176 (declaim (inline mutex-value-address))
177 #!+sb-thread
178 (defun mutex-value-address (mutex)
179   (declare (optimize (speed 3)))
180   (sb!ext:truly-the
181    sb!vm:word
182    (+ (sb!kernel:get-lisp-obj-address mutex)
183       (- (* 3 sb!vm:n-word-bytes) sb!vm:instance-pointer-lowtag))))
184
185 (defun get-mutex (mutex &optional (new-value *current-thread*) (wait-p t))
186   #!+sb-doc
187   "Acquire MUTEX, setting it to NEW-VALUE or some suitable default
188 value if NIL.  If WAIT-P is non-NIL and the mutex is in use, sleep
189 until it is available"
190   (declare (type mutex mutex) (optimize (speed 3)))
191   (unless new-value
192     (setq new-value *current-thread*))
193   #!-sb-thread
194   (let ((old-value (mutex-value mutex)))
195     (when (and old-value wait-p)
196       (error "In unithread mode, mutex ~S was requested with WAIT-P ~S and ~
197               new-value ~S, but has already been acquired (with value ~S)."
198              mutex wait-p new-value old-value))
199     (setf (mutex-value mutex) new-value)
200     t)
201   #!+sb-thread
202   (let (old)
203     (when (eql new-value (mutex-value mutex))
204       (warn "recursive lock attempt ~S~%" mutex)
205       (format *debug-io* "Thread: ~A~%" *current-thread*)
206       (sb!debug:backtrace most-positive-fixnum *debug-io*)
207       (force-output *debug-io*))
208     (loop
209      (unless
210          (setf old (sb!vm::%instance-set-conditional mutex 2 nil new-value))
211        (return t))
212      (unless wait-p (return nil))
213      (with-pinned-objects (mutex old)
214        (futex-wait (mutex-value-address mutex)
215                    (sb!kernel:get-lisp-obj-address old))))))
216
217 (defun release-mutex (mutex)
218   #!+sb-doc
219   "Release MUTEX by setting it to NIL. Wake up threads waiting for
220 this mutex."
221   (declare (type mutex mutex))
222   (setf (mutex-value mutex) nil)
223   #!+sb-thread
224   (futex-wake (mutex-value-address mutex) 1))
225
226 ;;;; waitqueues/condition variables
227
228 (defstruct (waitqueue (:constructor %make-waitqueue))
229   #!+sb-doc
230   "Waitqueue type."
231   (name nil :type (or null simple-string))
232   (data nil))
233
234 (defun make-waitqueue (&key name)
235   #!+sb-doc
236   "Create a waitqueue."
237   (%make-waitqueue :name name))
238
239 #!+sb-doc
240 (setf (sb!kernel:fdocumentation 'waitqueue-name 'function)
241       "The name of the waitqueue. Setfable.")
242
243 #!+sb-thread
244 (declaim (inline waitqueue-data-address))
245 #!+sb-thread
246 (defun waitqueue-data-address (waitqueue)
247   (declare (optimize (speed 3)))
248   (sb!ext:truly-the
249    sb!vm:word
250    (+ (sb!kernel:get-lisp-obj-address waitqueue)
251       (- (* 3 sb!vm:n-word-bytes) sb!vm:instance-pointer-lowtag))))
252
253 (defun condition-wait (queue mutex)
254   #!+sb-doc
255   "Atomically release MUTEX and enqueue ourselves on QUEUE.  Another
256 thread may subsequently notify us using CONDITION-NOTIFY, at which
257 time we reacquire MUTEX and return to the caller."
258   #!-sb-thread (declare (ignore queue))
259   (assert mutex)
260   #!-sb-thread (error "Not supported in unithread builds.")
261   #!+sb-thread
262   (let ((value (mutex-value mutex)))
263     (unwind-protect
264          (let ((me *current-thread*))
265            ;; XXX we should do something to ensure that the result of this setf
266            ;; is visible to all CPUs
267            (setf (waitqueue-data queue) me)
268            (release-mutex mutex)
269            ;; Now we go to sleep using futex-wait.  If anyone else
270            ;; manages to grab MUTEX and call CONDITION-NOTIFY during
271            ;; this comment, it will change queue->data, and so
272            ;; futex-wait returns immediately instead of sleeping.
273            ;; Ergo, no lost wakeup
274            (with-pinned-objects (queue me)
275              (futex-wait (waitqueue-data-address queue)
276                          (sb!kernel:get-lisp-obj-address me))))
277       ;; If we are interrupted while waiting, we should do these things
278       ;; before returning.  Ideally, in the case of an unhandled signal,
279       ;; we should do them before entering the debugger, but this is
280       ;; better than nothing.
281       (get-mutex mutex value))))
282
283 (defun condition-notify (queue &optional (n 1))
284   #!+sb-doc
285   "Notify N threads waiting on QUEUE."
286   #!-sb-thread (declare (ignore queue n))
287   #!-sb-thread (error "Not supported in unithread builds.")
288   #!+sb-thread
289   (declare (type (and fixnum (integer 1)) n))
290   #!+sb-thread
291   (let ((me *current-thread*))
292     ;; no problem if >1 thread notifies during the comment in
293     ;; condition-wait: as long as the value in queue-data isn't the
294     ;; waiting thread's id, it matters not what it is
295     ;; XXX we should do something to ensure that the result of this setf
296     ;; is visible to all CPUs
297     (setf (waitqueue-data queue) me)
298     (with-pinned-objects (queue)
299       (futex-wake (waitqueue-data-address queue) n))))
300
301 (defun condition-broadcast (queue)
302   #!+sb-doc
303   "Notify all threads waiting on QUEUE."
304   (condition-notify queue most-positive-fixnum))
305
306 ;;;; semaphores
307
308 (defstruct (semaphore (:constructor %make-semaphore))
309   #!+sb-doc
310   "Semaphore type."
311   (name nil :type (or null simple-string))
312   (count 0 :type (integer 0))
313   (mutex (make-mutex))
314   (queue (make-waitqueue)))
315
316 (defun make-semaphore (&key name (count 0))
317   #!+sb-doc
318   "Create a semaphore with the supplied COUNT."
319   (%make-semaphore :name name :count count))
320
321 (setf (sb!kernel:fdocumentation 'semaphore-name 'function)
322       "The name of the semaphore. Setfable.")
323
324 (defun wait-on-semaphore (sem)
325   #!+sb-doc
326   "Decrement the count of SEM if the count would not be negative. Else
327 block until the semaphore can be decremented."
328   ;; a more direct implementation based directly on futexes should be
329   ;; possible
330   (with-mutex ((semaphore-mutex sem))
331     (loop until (> (semaphore-count sem) 0)
332           do (condition-wait (semaphore-queue sem) (semaphore-mutex sem))
333           finally (decf (semaphore-count sem)))))
334
335 (defun signal-semaphore (sem &optional (n 1))
336   #!+sb-doc
337   "Increment the count of SEM by N. If there are threads waiting on
338 this semaphore, then N of them is woken up."
339   (declare (type (and fixnum (integer 1)) n))
340   (with-mutex ((semaphore-mutex sem))
341     (when (= n (incf (semaphore-count sem) n))
342       (condition-notify (semaphore-queue sem) n))))
343
344 ;;;; job control, independent listeners
345
346 (defstruct session
347   (lock (make-mutex :name "session lock"))
348   (threads nil)
349   (interactive-threads nil)
350   (interactive-threads-queue (make-waitqueue)))
351
352 (defvar *session* nil)
353
354 ;;; the debugger itself tries to acquire the session lock, don't let
355 ;;; funny situations (like getting a sigint while holding the session
356 ;;; lock) occur
357 (defmacro with-session-lock ((session) &body body)
358   #!-sb-thread (declare (ignore session))
359   #!-sb-thread
360   `(locally ,@body)
361   #!+sb-thread
362   `(without-interrupts
363     (with-mutex ((session-lock ,session))
364       ,@body)))
365
366 (defun new-session ()
367   (make-session :threads (list *current-thread*)
368                 :interactive-threads (list *current-thread*)))
369
370 (defun init-job-control ()
371   (setf *session* (new-session)))
372
373 (defun %delete-thread-from-session (thread session)
374   (with-session-lock (session)
375     (setf (session-threads session)
376           (delete thread (session-threads session))
377           (session-interactive-threads session)
378           (delete thread (session-interactive-threads session)))))
379
380 (defun call-with-new-session (fn)
381   (%delete-thread-from-session *current-thread* *session*)
382   (let ((*session* (new-session)))
383     (funcall fn)))
384
385 (defmacro with-new-session (args &body forms)
386   (declare (ignore args))               ;for extensibility
387   (sb!int:with-unique-names (fb-name)
388     `(labels ((,fb-name () ,@forms))
389       (call-with-new-session (function ,fb-name)))))
390
391 ;;; Remove thread from its session, if it has one.
392 #!+sb-thread
393 (defun handle-thread-exit (thread)
394   (with-mutex (*all-threads-lock*)
395     (setq *all-threads* (delete thread *all-threads*)))
396   (when *session*
397     (%delete-thread-from-session thread *session*)))
398
399 (defun terminate-session ()
400   #!+sb-doc
401   "Kill all threads in session except for this one.  Does nothing if current
402 thread is not the foreground thread."
403   ;; FIXME: threads created in other threads may escape termination
404   (let ((to-kill
405          (with-session-lock (*session*)
406            (and (eq *current-thread*
407                     (car (session-interactive-threads *session*)))
408                 (session-threads *session*)))))
409     ;; do the kill after dropping the mutex; unwind forms in dying
410     ;; threads may want to do session things
411     (dolist (thread to-kill)
412       (unless (eq thread *current-thread*)
413         ;; terminate the thread but don't be surprised if it has
414         ;; exited in the meantime
415         (handler-case (terminate-thread thread)
416           (interrupt-thread-error ()))))))
417
418 ;;; called from top of invoke-debugger
419 (defun debugger-wait-until-foreground-thread (stream)
420   "Returns T if thread had been running in background, NIL if it was
421 interactive."
422   (declare (ignore stream))
423   #!-sb-thread nil
424   #!+sb-thread
425   (prog1
426       (with-session-lock (*session*)
427         (not (member *current-thread*
428                      (session-interactive-threads *session*))))
429     (get-foreground)))
430
431 (defun get-foreground ()
432   #!-sb-thread t
433   #!+sb-thread
434   (let ((was-foreground t))
435     (loop
436      (with-session-lock (*session*)
437        (let ((int-t (session-interactive-threads *session*)))
438          (when (eq (car int-t) *current-thread*)
439            (unless was-foreground
440              (format *query-io* "Resuming thread ~A~%" *current-thread*))
441            (return-from get-foreground t))
442          (setf was-foreground nil)
443          (unless (member *current-thread* int-t)
444            (setf (cdr (last int-t))
445                  (list *current-thread*)))
446          (condition-wait
447           (session-interactive-threads-queue *session*)
448           (session-lock *session*)))))))
449
450 (defun release-foreground (&optional next)
451   #!+sb-doc
452   "Background this thread.  If NEXT is supplied, arrange for it to
453 have the foreground next."
454   #!-sb-thread (declare (ignore next))
455   #!-sb-thread nil
456   #!+sb-thread
457   (with-session-lock (*session*)
458     (when (rest (session-interactive-threads *session*))
459       (setf (session-interactive-threads *session*)
460             (delete *current-thread* (session-interactive-threads *session*))))
461     (when next
462       (setf (session-interactive-threads *session*)
463             (list* next
464                    (delete next (session-interactive-threads *session*)))))
465     (condition-broadcast (session-interactive-threads-queue *session*))))
466
467 (defun foreground-thread ()
468   (car (session-interactive-threads *session*)))
469
470 (defun make-listener-thread (tty-name)
471   (assert (probe-file tty-name))
472   (let* ((in (sb!unix:unix-open (namestring tty-name) sb!unix:o_rdwr #o666))
473          (out (sb!unix:unix-dup in))
474          (err (sb!unix:unix-dup in)))
475     (labels ((thread-repl ()
476                (sb!unix::unix-setsid)
477                (let* ((sb!impl::*stdin*
478                        (make-fd-stream in :input t :buffering :line
479                                               :dual-channel-p t))
480                       (sb!impl::*stdout*
481                        (make-fd-stream out :output t :buffering :line
482                                               :dual-channel-p t))
483                       (sb!impl::*stderr*
484                        (make-fd-stream err :output t :buffering :line
485                                               :dual-channel-p t))
486                       (sb!impl::*tty*
487                        (make-fd-stream err :input t :output t
488                                               :buffering :line
489                                               :dual-channel-p t))
490                       (sb!impl::*descriptor-handlers* nil))
491                  (with-new-session ()
492                    (unwind-protect
493                         (sb!impl::toplevel-repl nil)
494                      (sb!int:flush-standard-output-streams))))))
495       (make-thread #'thread-repl))))
496
497 ;;;; the beef
498
499 (defun make-thread (function &key name)
500   #!+sb-doc
501   "Create a new thread of NAME that runs FUNCTION. When the function
502 returns the thread exits."
503   #!-sb-thread (declare (ignore function name))
504   #!-sb-thread (error "Not supported in unithread builds.")
505   #!+sb-thread
506   (let* ((thread (%make-thread :name name))
507          (setup-sem (make-semaphore :name "Thread setup semaphore"))
508          (real-function (coerce function 'function))
509          (initial-function
510           (lambda ()
511             ;; in time we'll move some of the binding presently done in C
512             ;; here too
513             (let ((*current-thread* thread)
514                   (sb!kernel::*restart-clusters* nil)
515                   (sb!kernel::*handler-clusters* nil)
516                   (sb!kernel::*condition-restarts* nil)
517                   (sb!impl::*descriptor-handlers* nil)) ; serve-event
518               (setf (thread-os-thread thread) (current-thread-sap-id))
519               (with-mutex (*all-threads-lock*)
520                 (push thread *all-threads*))
521               (with-session-lock (*session*)
522                 (push thread (session-threads *session*)))
523               (setf (thread-%alive-p thread) t)
524               (signal-semaphore setup-sem)
525               ;; can't use handling-end-of-the-world, because that flushes
526               ;; output streams, and we don't necessarily have any (or we
527               ;; could be sharing them)
528               (catch 'sb!impl::toplevel-catcher
529                 (catch 'sb!impl::%end-of-the-world
530                   (with-simple-restart
531                       (terminate-thread
532                        (format nil
533                                "~~@<Terminate this thread (~A)~~@:>"
534                                *current-thread*))
535                     (unwind-protect
536                          (progn
537                            ;; now that most things have a chance to
538                            ;; work properly without messing up other
539                            ;; threads, it's time to enable signals
540                            (sb!unix::reset-signal-mask)
541                            (funcall real-function))
542                       ;; we're going down, can't handle
543                       ;; interrupts sanely anymore
544                       (let ((sb!impl::*gc-inhibit* t))
545                         (block-blockable-signals)
546                         (setf (thread-%alive-p thread) nil)
547                         (setf (thread-os-thread thread) nil)
548                         ;; and remove what can be the last
549                         ;; reference to this thread
550                         (handle-thread-exit thread)))))))
551             (values))))
552     (let ((os-thread
553            (with-pinned-objects (initial-function)
554              (%create-thread
555               (sb!kernel:get-lisp-obj-address initial-function)))))
556       (when (zerop os-thread)
557         (error "Can't create a new thread"))
558       (wait-on-semaphore setup-sem)
559       thread)))
560
561 (defun destroy-thread (thread)
562   #!+sb-doc
563   "Deprecated. Same as TERMINATE-THREAD."
564   (terminate-thread thread))
565
566 (define-condition interrupt-thread-error (error)
567   ((thread :reader interrupt-thread-error-thread :initarg :thread))
568   #!+sb-doc
569   (:documentation "Interrupting thread failed.")
570   (:report (lambda (c s)
571              (format s "Interrupt thread failed: thread ~A has exited."
572                      (interrupt-thread-error-thread c)))))
573
574 #!+sb-doc
575 (setf (sb!kernel:fdocumentation 'interrupt-thread-error-thread 'function)
576       "The thread that was not interrupted.")
577
578 (defmacro with-interruptions-lock ((thread) &body body)
579   `(without-interrupts
580      (with-mutex ((thread-interruptions-lock ,thread))
581        ,@body)))
582
583 ;; Called from the signal handler.
584 (defun run-interruption ()
585   (in-interruption ()
586    (let ((interruption (with-interruptions-lock (*current-thread*)
587                          (pop (thread-interruptions *current-thread*)))))
588      (with-interrupts
589        (funcall interruption)))))
590
591 ;; The order of interrupt execution is peculiar. If thread A
592 ;; interrupts thread B with I1, I2 and B for some reason receives I1
593 ;; when FUN2 is already on the list, then it is FUN2 that gets to run
594 ;; first. But when FUN2 is run SIG_INTERRUPT_THREAD is enabled again
595 ;; and I2 hits pretty soon in FUN2 and run FUN1. This is of course
596 ;; just one scenario, and the order of thread interrupt execution is
597 ;; undefined.
598 (defun interrupt-thread (thread function)
599   #!+sb-doc
600   "Interrupt the live THREAD and make it run FUNCTION. A moderate
601 degree of care is expected for use of INTERRUPT-THREAD, due to its
602 nature: if you interrupt a thread that was holding important locks
603 then do something that turns out to need those locks, you probably
604 won't like the effect."
605   #!-sb-thread (declare (ignore thread))
606   ;; not quite perfect, because it does not take WITHOUT-INTERRUPTS
607   ;; into account
608   #!-sb-thread
609   (funcall function)
610   #!+sb-thread
611   (if (eq thread *current-thread*)
612       (funcall function)
613       (let ((os-thread (thread-os-thread thread)))
614         (cond ((not os-thread)
615                (error 'interrupt-thread-error :thread thread))
616               (t
617                (with-interruptions-lock (thread)
618                  (push function (thread-interruptions thread)))
619                (when (minusp (signal-interrupt-thread os-thread))
620                  (error 'interrupt-thread-error :thread thread)))))))
621
622 (defun terminate-thread (thread)
623   #!+sb-doc
624   "Terminate the thread identified by THREAD, by causing it to run
625 SB-EXT:QUIT - the usual cleanup forms will be evaluated"
626   (interrupt-thread thread 'sb!ext:quit))
627
628 ;;; internal use only.  If you think you need to use this, either you
629 ;;; are an SBCL developer, are doing something that you should discuss
630 ;;; with an SBCL developer first, or are doing something that you
631 ;;; should probably discuss with a professional psychiatrist first
632 #!+sb-thread
633 (defun thread-sap-for-id (id)
634   (let ((thread-sap (alien-sap (extern-alien "all_threads" (* t)))))
635     (loop
636      (when (sap= thread-sap (int-sap 0)) (return nil))
637      (let ((os-thread (sap-ref-word thread-sap
638                                     (* sb!vm:n-word-bytes
639                                        sb!vm::thread-os-thread-slot))))
640        (when (= os-thread id) (return thread-sap))
641        (setf thread-sap
642              (sap-ref-sap thread-sap (* sb!vm:n-word-bytes
643                                         sb!vm::thread-next-slot)))))))
644
645 #!+sb-thread
646 (defun symbol-value-in-thread (symbol thread-sap)
647   (let* ((index (sb!vm::symbol-tls-index symbol))
648          (tl-val (sap-ref-word thread-sap
649                                (* sb!vm:n-word-bytes index))))
650     (if (eql tl-val sb!vm::no-tls-value-marker-widetag)
651         (sb!vm::symbol-global-value symbol)
652         (sb!kernel:make-lisp-obj tl-val))))