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