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