Rename "boehm-gc.h" to "bdw-gc.h"; add to the distribution.
[bpt/guile.git] / doc / ref / api-scheduling.texi
CommitLineData
07d83abe
MV
1@c -*-texinfo-*-
2@c This is part of the GNU Guile Reference Manual.
07e02175 3@c Copyright (C) 1996, 1997, 2000, 2001, 2002, 2003, 2004, 2007
07d83abe
MV
4@c Free Software Foundation, Inc.
5@c See the file guile.texi for copying conditions.
6
7@page
8@node Scheduling
9@section Threads, Mutexes, Asyncs and Dynamic Roots
10
07d83abe
MV
11@menu
12* Arbiters:: Synchronization primitives.
13* Asyncs:: Asynchronous procedure invocation.
07d83abe 14* Threads:: Multiple threads of execution.
2567692a 15* Mutexes and Condition Variables:: Synchronization primitives.
b4fddbbe 16* Blocking:: How to block properly in guile mode.
2567692a 17* Critical Sections:: Avoiding concurrency and reentries.
b4fddbbe 18* Fluids and Dynamic States:: Thread-local variables, etc.
07d83abe
MV
19* Parallel Forms:: Parallel execution of forms.
20@end menu
21
22
23@node Arbiters
24@subsection Arbiters
07d83abe
MV
25@cindex arbiters
26
e136aab0
KR
27Arbiters are synchronization objects, they can be used by threads to
28control access to a shared resource. An arbiter can be locked to
29indicate a resource is in use, and unlocked when done.
07d83abe 30
b4fddbbe
MV
31An arbiter is like a light-weight mutex (@pxref{Mutexes and Condition
32Variables}). It uses less memory and may be faster, but there's no
33way for a thread to block waiting on an arbiter, it can only test and
34get the status returned.
07d83abe
MV
35
36@deffn {Scheme Procedure} make-arbiter name
37@deffnx {C Function} scm_make_arbiter (name)
cdf1ad3b
MV
38Return an object of type arbiter and name @var{name}. Its
39state is initially unlocked. Arbiters are a way to achieve
40process synchronization.
07d83abe
MV
41@end deffn
42
43@deffn {Scheme Procedure} try-arbiter arb
44@deffnx {C Function} scm_try_arbiter (arb)
cdf1ad3b
MV
45If @var{arb} is unlocked, then lock it and return @code{#t}.
46If @var{arb} is already locked, then do nothing and return
47@code{#f}.
07d83abe
MV
48@end deffn
49
50@deffn {Scheme Procedure} release-arbiter arb
51@deffnx {C Function} scm_release_arbiter (arb)
e136aab0
KR
52If @var{arb} is locked, then unlock it and return @code{#t}. If
53@var{arb} is already unlocked, then do nothing and return @code{#f}.
54
55Typical usage is for the thread which locked an arbiter to later
56release it, but that's not required, any thread can release it.
07d83abe
MV
57@end deffn
58
59
60@node Asyncs
61@subsection Asyncs
62
63@cindex asyncs
64@cindex user asyncs
65@cindex system asyncs
66
1021bb7a 67Asyncs are a means of deferring the execution of Scheme code until it is
07d83abe
MV
68safe to do so.
69
70Guile provides two kinds of asyncs that share the basic concept but are
71otherwise quite different: system asyncs and user asyncs. System asyncs
72are integrated into the core of Guile and are executed automatically
73when the system is in a state to allow the execution of Scheme code.
74For example, it is not possible to execute Scheme code in a POSIX signal
75handler, but such a signal handler can queue a system async to be
76executed in the near future, when it is safe to do so.
77
78System asyncs can also be queued for threads other than the current one.
79This way, you can cause threads to asynchronously execute arbitrary
80code.
81
82User asyncs offer a convenient means of queueing procedures for future
83execution and triggering this execution. They will not be executed
84automatically.
85
86@menu
74926120
NJ
87* System asyncs::
88* User asyncs::
07d83abe
MV
89@end menu
90
91@node System asyncs
92@subsubsection System asyncs
93
94To cause the future asynchronous execution of a procedure in a given
95thread, use @code{system-async-mark}.
96
97Automatic invocation of system asyncs can be temporarily disabled by
98calling @code{call-with-blocked-asyncs}. This function works by
99temporarily increasing the @emph{async blocking level} of the current
100thread while a given procedure is running. The blocking level starts
101out at zero, and whenever a safe point is reached, a blocking level
102greater than zero will prevent the execution of queued asyncs.
103
104Analogously, the procedure @code{call-with-unblocked-asyncs} will
105temporarily decrease the blocking level of the current thread. You
106can use it when you want to disable asyncs by default and only allow
107them temporarily.
108
109In addition to the C versions of @code{call-with-blocked-asyncs} and
110@code{call-with-unblocked-asyncs}, C code can use
661ae7ab
MV
111@code{scm_dynwind_block_asyncs} and @code{scm_dynwind_unblock_asyncs}
112inside a @dfn{dynamic context} (@pxref{Dynamic Wind}) to block or
113unblock system asyncs temporarily.
07d83abe
MV
114
115@deffn {Scheme Procedure} system-async-mark proc [thread]
116@deffnx {C Function} scm_system_async_mark (proc)
117@deffnx {C Function} scm_system_async_mark_for_thread (proc, thread)
118Mark @var{proc} (a procedure with zero arguments) for future execution
119in @var{thread}. When @var{proc} has already been marked for
120@var{thread} but has not been executed yet, this call has no effect.
121When @var{thread} is omitted, the thread that called
122@code{system-async-mark} is used.
123
124This procedure is not safe to be called from signal handlers. Use
125@code{scm_sigaction} or @code{scm_sigaction_for_thread} to install
126signal handlers.
127@end deffn
128
07d83abe
MV
129@deffn {Scheme Procedure} call-with-blocked-asyncs proc
130@deffnx {C Function} scm_call_with_blocked_asyncs (proc)
07d83abe
MV
131Call @var{proc} and block the execution of system asyncs by one level
132for the current thread while it is running. Return the value returned
133by @var{proc}. For the first two variants, call @var{proc} with no
134arguments; for the third, call it with @var{data}.
135@end deffn
136
1021bb7a
NJ
137@deftypefn {C Function} {void *} scm_c_call_with_blocked_asyncs (void * (*proc) (void *data), void *data)
138The same but with a C function @var{proc} instead of a Scheme thunk.
139@end deftypefn
140
07d83abe
MV
141@deffn {Scheme Procedure} call-with-unblocked-asyncs proc
142@deffnx {C Function} scm_call_with_unblocked_asyncs (proc)
07d83abe
MV
143Call @var{proc} and unblock the execution of system asyncs by one
144level for the current thread while it is running. Return the value
145returned by @var{proc}. For the first two variants, call @var{proc}
146with no arguments; for the third, call it with @var{data}.
147@end deffn
148
1021bb7a
NJ
149@deftypefn {C Function} {void *} scm_c_call_with_unblocked_asyncs (void *(*proc) (void *data), void *data)
150The same but with a C function @var{proc} instead of a Scheme thunk.
151@end deftypefn
152
661ae7ab 153@deftypefn {C Function} void scm_dynwind_block_asyncs ()
1021bb7a
NJ
154During the current dynwind context, increase the blocking of asyncs by
155one level. This function must be used inside a pair of calls to
661ae7ab 156@code{scm_dynwind_begin} and @code{scm_dynwind_end} (@pxref{Dynamic
1021bb7a 157Wind}).
07d83abe
MV
158@end deftypefn
159
661ae7ab 160@deftypefn {C Function} void scm_dynwind_unblock_asyncs ()
1021bb7a
NJ
161During the current dynwind context, decrease the blocking of asyncs by
162one level. This function must be used inside a pair of calls to
661ae7ab 163@code{scm_dynwind_begin} and @code{scm_dynwind_end} (@pxref{Dynamic
1021bb7a 164Wind}).
07d83abe
MV
165@end deftypefn
166
167@node User asyncs
168@subsubsection User asyncs
169
170A user async is a pair of a thunk (a parameterless procedure) and a
171mark. Setting the mark on a user async will cause the thunk to be
172executed when the user async is passed to @code{run-asyncs}. Setting
173the mark more than once is satisfied by one execution of the thunk.
174
175User asyncs are created with @code{async}. They are marked with
176@code{async-mark}.
177
178@deffn {Scheme Procedure} async thunk
179@deffnx {C Function} scm_async (thunk)
180Create a new user async for the procedure @var{thunk}.
181@end deffn
182
183@deffn {Scheme Procedure} async-mark a
184@deffnx {C Function} scm_async_mark (a)
185Mark the user async @var{a} for future execution.
186@end deffn
187
188@deffn {Scheme Procedure} run-asyncs list_of_a
189@deffnx {C Function} scm_run_asyncs (list_of_a)
190Execute all thunks from the marked asyncs of the list @var{list_of_a}.
191@end deffn
192
07d83abe
MV
193@node Threads
194@subsection Threads
195@cindex threads
196@cindex Guile threads
197@cindex POSIX threads
198
cdf1ad3b
MV
199@deffn {Scheme Procedure} all-threads
200@deffnx {C Function} scm_all_threads ()
201Return a list of all threads.
202@end deffn
203
204@deffn {Scheme Procedure} current-thread
205@deffnx {C Function} scm_current_thread ()
206Return the thread that called this function.
207@end deffn
07d83abe
MV
208
209@c begin (texi-doc-string "guile" "call-with-new-thread")
23f2b9a3 210@deffn {Scheme Procedure} call-with-new-thread thunk [handler]
b4fddbbe
MV
211Call @code{thunk} in a new thread and with a new dynamic state,
212returning the new thread. The procedure @var{thunk} is called via
213@code{with-continuation-barrier}.
07d83abe 214
b4fddbbe
MV
215When @var{handler} is specified, then @var{thunk} is called from
216within a @code{catch} with tag @code{#t} that has @var{handler} as its
217handler. This catch is established inside the continuation barrier.
07d83abe 218
b4fddbbe
MV
219Once @var{thunk} or @var{handler} returns, the return value is made
220the @emph{exit value} of the thread and the thread is terminated.
07d83abe
MV
221@end deffn
222
b4fddbbe
MV
223@deftypefn {C Function} SCM scm_spawn_thread (scm_t_catch_body body, void *body_data, scm_t_catch_handler handler, void *handler_data)
224Call @var{body} in a new thread, passing it @var{body_data}, returning
225the new thread. The function @var{body} is called via
226@code{scm_c_with_continuation_barrier}.
227
228When @var{handler} is non-@code{NULL}, @var{body} is called via
229@code{scm_internal_catch} with tag @code{SCM_BOOL_T} that has
230@var{handler} and @var{handler_data} as the handler and its data. This
231catch is established inside the continuation barrier.
232
233Once @var{body} or @var{handler} returns, the return value is made the
234@emph{exit value} of the thread and the thread is terminated.
235@end deftypefn
236
6180e336
NJ
237@deffn {Scheme Procedure} thread? obj
238@deffnx {C Function} scm_thread_p (obj)
239Return @code{#t} iff @var{obj} is a thread; otherwise, return
240@code{#f}.
241@end deffn
242
07d83abe 243@c begin (texi-doc-string "guile" "join-thread")
6180e336 244@deffn {Scheme Procedure} join-thread thread [timeout [timeoutval]]
300b1ae5 245@deffnx {C Function} scm_join_thread (thread)
6180e336 246@deffnx {C Function} scm_join_thread_timed (thread, timeout, timeoutval)
b4fddbbe
MV
247Wait for @var{thread} to terminate and return its exit value. Threads
248that have not been created with @code{call-with-new-thread} or
74926120 249@code{scm_spawn_thread} have an exit value of @code{#f}. When
6180e336 250@var{timeout} is given, it specifies a point in time where the waiting
74926120
NJ
251should be aborted. It can be either an integer as returned by
252@code{current-time} or a pair as returned by @code{gettimeofday}.
253When the waiting is aborted, @var{timeoutval} is returned (if it is
6180e336 254specified; @code{#f} is returned otherwise).
07d83abe
MV
255@end deffn
256
cdf1ad3b
MV
257@deffn {Scheme Procedure} thread-exited? thread
258@deffnx {C Function} scm_thread_exited_p (thread)
259Return @code{#t} iff @var{thread} has exited.
260@end deffn
261
07d83abe
MV
262@c begin (texi-doc-string "guile" "yield")
263@deffn {Scheme Procedure} yield
264If one or more threads are waiting to execute, calling yield forces an
265immediate context switch to one of them. Otherwise, yield has no effect.
266@end deffn
267
07e02175
LC
268@deffn {Scheme Procedure} cancel-thread thread
269@deffnx {C Function} scm_cancel_thread (thread)
270Asynchronously notify @var{thread} to exit. Immediately after
271receiving this notification, @var{thread} will call its cleanup handler
272(if one has been set) and then terminate, aborting any evaluation that
273is in progress.
274
275Because Guile threads are isomorphic with POSIX threads, @var{thread}
276will not receive its cancellation signal until it reaches a cancellation
277point. See your operating system's POSIX threading documentation for
278more information on cancellation points; note that in Guile, unlike
279native POSIX threads, a thread can receive a cancellation notification
280while attempting to lock a mutex.
281@end deffn
282
283@deffn {Scheme Procedure} set-thread-cleanup! thread proc
284@deffnx {C Function} scm_set_thread_cleanup_x (thread, proc)
285Set @var{proc} as the cleanup handler for the thread @var{thread}.
286@var{proc}, which must be a thunk, will be called when @var{thread}
287exits, either normally or by being canceled. Thread cleanup handlers
288can be used to perform useful tasks like releasing resources, such as
289locked mutexes, when thread exit cannot be predicted.
290
291The return value of @var{proc} will be set as the @emph{exit value} of
292@var{thread}.
293
294To remove a cleanup handler, pass @code{#f} for @var{proc}.
295@end deffn
296
297@deffn {Scheme Procedure} thread-cleanup thread
298@deffnx {C Function} scm_thread_cleanup (thread)
299Return the cleanup handler currently installed for the thread
300@var{thread}. If no cleanup handler is currently installed,
301thread-cleanup returns @code{#f}.
302@end deffn
303
07d83abe
MV
304Higher level thread procedures are available by loading the
305@code{(ice-9 threads)} module. These provide standardized
3cf066df 306thread creation.
07d83abe
MV
307
308@deffn macro make-thread proc [args@dots{}]
309Apply @var{proc} to @var{args} in a new thread formed by
310@code{call-with-new-thread} using a default error handler that display
b4fddbbe
MV
311the error to the current error port. The @var{args@dots{}}
312expressions are evaluated in the new thread.
07d83abe
MV
313@end deffn
314
315@deffn macro begin-thread first [rest@dots{}]
316Evaluate forms @var{first} and @var{rest} in a new thread formed by
317@code{call-with-new-thread} using a default error handler that display
318the error to the current error port.
319@end deffn
320
2567692a
MV
321@node Mutexes and Condition Variables
322@subsection Mutexes and Condition Variables
323@cindex mutex
324@cindex condition variable
325
326A mutex is a thread synchronization object, it can be used by threads
327to control access to a shared resource. A mutex can be locked to
328indicate a resource is in use, and other threads can then block on the
329mutex to wait for the resource (or can just test and do something else
330if not available). ``Mutex'' is short for ``mutual exclusion''.
331
332There are two types of mutexes in Guile, ``standard'' and
333``recursive''. They're created by @code{make-mutex} and
334@code{make-recursive-mutex} respectively, the operation functions are
335then common to both.
336
337Note that for both types of mutex there's no protection against a
338``deadly embrace''. For instance if one thread has locked mutex A and
339is waiting on mutex B, but another thread owns B and is waiting on A,
340then an endless wait will occur (in the current implementation).
341Acquiring requisite mutexes in a fixed order (like always A before B)
342in all threads is one way to avoid such problems.
343
344@sp 1
6180e336 345@deffn {Scheme Procedure} make-mutex . flags
2567692a 346@deffnx {C Function} scm_make_mutex ()
9c9b203b 347@deffnx {C Function} scm_make_mutex_with_flags (SCM flags)
74926120 348Return a new mutex. It is initially unlocked. If @var{flags} is
6180e336 349specified, it must be a list of symbols specifying configuration flags
74926120 350for the newly-created mutex. The supported flags are:
6180e336
NJ
351@table @code
352@item unchecked-unlock
353Unless this flag is present, a call to `unlock-mutex' on the returned
354mutex when it is already unlocked will cause an error to be signalled.
355
356@item allow-external-unlock
357Allow the returned mutex to be unlocked by the calling thread even if
358it was originally locked by a different thread.
359
360@item recursive
361The returned mutex will be recursive.
362
363@end table
364@end deffn
365
366@deffn {Scheme Procedure} mutex? obj
367@deffnx {C Function} scm_mutex_p (obj)
74926120 368Return @code{#t} iff @var{obj} is a mutex; otherwise, return
6180e336 369@code{#f}.
2567692a
MV
370@end deffn
371
372@deffn {Scheme Procedure} make-recursive-mutex
373@deffnx {C Function} scm_make_recursive_mutex ()
6180e336
NJ
374Create a new recursive mutex. It is initially unlocked. Calling this
375function is equivalent to calling `make-mutex' and specifying the
376@code{recursive} flag.
2567692a
MV
377@end deffn
378
adc085f1 379@deffn {Scheme Procedure} lock-mutex mutex [timeout [owner]]
2567692a 380@deffnx {C Function} scm_lock_mutex (mutex)
adc085f1 381@deffnx {C Function} scm_lock_mutex_timed (mutex, timeout, owner)
74926120 382Lock @var{mutex}. If the mutex is already locked, then block and
adc085f1 383return only when @var{mutex} has been acquired.
2567692a 384
74926120
NJ
385When @var{timeout} is given, it specifies a point in time where the
386waiting should be aborted. It can be either an integer as returned
387by @code{current-time} or a pair as returned by @code{gettimeofday}.
388When the waiting is aborted, @code{#f} is returned.
6180e336 389
adc085f1 390When @var{owner} is given, it specifies an owner for @var{mutex} other
74926120 391than the calling thread. @var{owner} may also be @code{#f},
adc085f1
JG
392indicating that the mutex should be locked but left unowned.
393
2567692a
MV
394For standard mutexes (@code{make-mutex}), and error is signalled if
395the thread has itself already locked @var{mutex}.
396
397For a recursive mutex (@code{make-recursive-mutex}), if the thread has
398itself already locked @var{mutex}, then a further @code{lock-mutex}
399call increments the lock count. An additional @code{unlock-mutex}
400will be required to finally release.
401
6180e336 402If @var{mutex} was locked by a thread that exited before unlocking it,
74926120 403the next attempt to lock @var{mutex} will succeed, but
6180e336
NJ
404@code{abandoned-mutex-error} will be signalled.
405
2567692a
MV
406When a system async (@pxref{System asyncs}) is activated for a thread
407blocked in @code{lock-mutex}, the wait is interrupted and the async is
408executed. When the async returns, the wait resumes.
409@end deffn
410
661ae7ab
MV
411@deftypefn {C Function} void scm_dynwind_lock_mutex (SCM mutex)
412Arrange for @var{mutex} to be locked whenever the current dynwind
413context is entered and to be unlocked when it is exited.
2567692a 414@end deftypefn
74926120 415
2567692a
MV
416@deffn {Scheme Procedure} try-mutex mx
417@deffnx {C Function} scm_try_mutex (mx)
418Try to lock @var{mutex} as per @code{lock-mutex}. If @var{mutex} can
419be acquired immediately then this is done and the return is @code{#t}.
420If @var{mutex} is locked by some other thread then nothing is done and
421the return is @code{#f}.
422@end deffn
423
6180e336 424@deffn {Scheme Procedure} unlock-mutex mutex [condvar [timeout]]
2567692a 425@deffnx {C Function} scm_unlock_mutex (mutex)
6180e336
NJ
426@deffnx {C Function} scm_unlock_mutex_timed (mutex, condvar, timeout)
427Unlock @var{mutex}. An error is signalled if @var{mutex} is not locked
74926120 428and was not created with the @code{unchecked-unlock} flag set, or if
6180e336
NJ
429@var{mutex} is locked by a thread other than the calling thread and was
430not created with the @code{allow-external-unlock} flag set.
431
432If @var{condvar} is given, it specifies a condition variable upon
433which the calling thread will wait to be signalled before returning.
74926120 434(This behavior is very similar to that of
6180e336
NJ
435@code{wait-condition-variable}, except that the mutex is left in an
436unlocked state when the function returns.)
437
74926120
NJ
438When @var{timeout} is also given, it specifies a point in time where
439the waiting should be aborted. It can be either an integer as
440returned by @code{current-time} or a pair as returned by
441@code{gettimeofday}. When the waiting is aborted, @code{#f} is
6180e336 442returned. Otherwise the function returns @code{#t}.
2567692a
MV
443@end deffn
444
adc085f1
JG
445@deffn {Scheme Procedure} mutex-owner mutex
446@deffnx {C Function} scm_mutex_owner (mutex)
74926120 447Return the current owner of @var{mutex}, in the form of a thread or
adc085f1
JG
448@code{#f} (indicating no owner). Note that a mutex may be unowned but
449still locked.
450@end deffn
451
452@deffn {Scheme Procedure} mutex-level mutex
453@deffnx {C Function} scm_mutex_level (mutex)
454Return the current lock level of @var{mutex}. If @var{mutex} is
455currently unlocked, this value will be 0; otherwise, it will be the
456number of times @var{mutex} has been recursively locked by its current
457owner.
458@end deffn
459
460@deffn {Scheme Procedure} mutex-locked? mutex
461@deffnx {C Function} scm_mutex_locked_p (mutex)
462Return @code{#t} if @var{mutex} is locked, regardless of ownership;
463otherwise, return @code{#f}.
464@end deffn
465
2567692a
MV
466@deffn {Scheme Procedure} make-condition-variable
467@deffnx {C Function} scm_make_condition_variable ()
468Return a new condition variable.
469@end deffn
470
6180e336
NJ
471@deffn {Scheme Procedure} condition-variable? obj
472@deffnx {C Function} scm_condition_variable_p (obj)
74926120 473Return @code{#t} iff @var{obj} is a condition variable; otherwise,
6180e336
NJ
474return @code{#f}.
475@end deffn
476
2567692a
MV
477@deffn {Scheme Procedure} wait-condition-variable condvar mutex [time]
478@deffnx {C Function} scm_wait_condition_variable (condvar, mutex, time)
479Wait until @var{condvar} has been signalled. While waiting,
480@var{mutex} is atomically unlocked (as with @code{unlock-mutex}) and
481is locked again when this function returns. When @var{time} is given,
482it specifies a point in time where the waiting should be aborted. It
483can be either a integer as returned by @code{current-time} or a pair
484as returned by @code{gettimeofday}. When the waiting is aborted,
485@code{#f} is returned. When the condition variable has in fact been
486signalled, @code{#t} is returned. The mutex is re-locked in any case
487before @code{wait-condition-variable} returns.
488
489When a system async is activated for a thread that is blocked in a
490call to @code{wait-condition-variable}, the waiting is interrupted,
491the mutex is locked, and the async is executed. When the async
492returns, the mutex is unlocked again and the waiting is resumed. When
493the thread block while re-acquiring the mutex, execution of asyncs is
494blocked.
495@end deffn
496
497@deffn {Scheme Procedure} signal-condition-variable condvar
498@deffnx {C Function} scm_signal_condition_variable (condvar)
499Wake up one thread that is waiting for @var{condvar}.
500@end deffn
501
502@deffn {Scheme Procedure} broadcast-condition-variable condvar
503@deffnx {C Function} scm_broadcast_condition_variable (condvar)
504Wake up all threads that are waiting for @var{condvar}.
505@end deffn
506
507@sp 1
508The following are higher level operations on mutexes. These are
509available from
510
511@example
512(use-modules (ice-9 threads))
513@end example
514
515@deffn macro with-mutex mutex [body@dots{}]
516Lock @var{mutex}, evaluate the @var{body} forms, then unlock
517@var{mutex}. The return value is the return from the last @var{body}
518form.
519
520The lock, body and unlock form the branches of a @code{dynamic-wind}
521(@pxref{Dynamic Wind}), so @var{mutex} is automatically unlocked if an
522error or new continuation exits @var{body}, and is re-locked if
523@var{body} is re-entered by a captured continuation.
524@end deffn
525
526@deffn macro monitor body@dots{}
527Evaluate the @var{body} forms, with a mutex locked so only one thread
528can execute that code at any one time. The return value is the return
529from the last @var{body} form.
530
531Each @code{monitor} form has its own private mutex and the locking and
532evaluation is as per @code{with-mutex} above. A standard mutex
533(@code{make-mutex}) is used, which means @var{body} must not
534recursively re-enter the @code{monitor} form.
535
536The term ``monitor'' comes from operating system theory, where it
537means a particular bit of code managing access to some resource and
538which only ever executes on behalf of one process at any one time.
539@end deffn
540
541
b4fddbbe
MV
542@node Blocking
543@subsection Blocking in Guile Mode
07d83abe 544
b4fddbbe
MV
545A thread must not block outside of a libguile function while it is in
546guile mode. The following functions can be used to temporily leave
547guile mode or to perform some common blocking operations in a supported
548way.
07d83abe 549
54428bb8
MV
550@deftypefn {C Function} {void *} scm_without_guile (void *(*func) (void *), void *data)
551Leave guile mode, call @var{func} on @var{data}, enter guile mode and
552return the result of calling @var{func}.
07d83abe 553
b4fddbbe 554While a thread has left guile mode, it must not call any libguile
54428bb8
MV
555functions except @code{scm_with_guile} or @code{scm_without_guile} and
556must not use any libguile macros. Also, local variables of type
557@code{SCM} that are allocated while not in guile mode are not
558protected from the garbage collector.
559
560When used from non-guile mode, calling @code{scm_without_guile} is
561still allowed: it simply calls @var{func}. In that way, you can leave
562guile mode without having to know whether the current thread is in
563guile mode or not.
07d83abe
MV
564@end deftypefn
565
b4fddbbe
MV
566@deftypefn {C Function} int scm_pthread_mutex_lock (pthread_mutex_t *mutex)
567Like @code{pthread_mutex_lock}, but leaves guile mode while waiting for
568the mutex.
07d83abe
MV
569@end deftypefn
570
b4fddbbe
MV
571@deftypefn {C Function} int scm_pthread_cond_wait (pthread_cond_t *cond, pthread_mutex_t *mutex)
572@deftypefnx {C Function} int scm_pthread_cond_timedwait (pthread_cond_t *cond, pthread_mutex_t *mutex, struct timespec *abstime)
573Like @code{pthread_cond_wait} and @code{pthread_cond_timedwait}, but
574leaves guile mode while waiting for the condition variable.
07d83abe
MV
575@end deftypefn
576
b4fddbbe
MV
577@deftypefn {C Function} int scm_std_select (int nfds, fd_set *readfds, fd_set *writefds, fd_set *exceptfds, struct timeval *timeout)
578Like @code{select} but leaves guile mode while waiting. Also, the
579delivery of a system async causes this function to be interrupted with
580error code @code{EINTR}.
07d83abe
MV
581@end deftypefn
582
b4fddbbe
MV
583@deftypefn {C Function} {unsigned int} scm_std_sleep ({unsigned int} seconds)
584Like @code{sleep}, but leaves guile mode while sleeping. Also, the
585delivery of a system async causes this function to be interrupted.
07d83abe
MV
586@end deftypefn
587
b4fddbbe
MV
588@deftypefn {C Function} {unsigned long} scm_std_usleep ({unsigned long} usecs)
589Like @code{usleep}, but leaves guile mode while sleeping. Also, the
590delivery of a system async causes this function to be interrupted.
07d83abe
MV
591@end deftypefn
592
07d83abe 593
2567692a
MV
594@node Critical Sections
595@subsection Critical Sections
596
597@deffn {C Macro} SCM_CRITICAL_SECTION_START
598@deffnx {C Macro} SCM_CRITICAL_SECTION_END
599These two macros can be used to delimit a critical section.
600Syntactically, they are both statements and need to be followed
601immediately by a semicolon.
602
603Executing @code{SCM_CRITICAL_SECTION_START} will lock a recursive
604mutex and block the executing of system asyncs. Executing
605@code{SCM_CRITICAL_SECTION_END} will unblock the execution of system
606asyncs and unlock the mutex. Thus, the code that executes between
607these two macros can only be executed in one thread at any one time
608and no system asyncs will run. However, because the mutex is a
609recursive one, the code might still be reentered by the same thread.
610You must either allow for this or avoid it, both by careful coding.
611
612On the other hand, critical sections delimited with these macros can
613be nested since the mutex is recursive.
614
615You must make sure that for each @code{SCM_CRITICAL_SECTION_START},
616the corresponding @code{SCM_CRITICAL_SECTION_END} is always executed.
617This means that no non-local exit (such as a signalled error) might
618happen, for example.
619@end deffn
620
661ae7ab
MV
621@deftypefn {C Function} void scm_dynwind_critical_section (SCM mutex)
622Call @code{scm_dynwind_lock_mutex} on @var{mutex} and call
623@code{scm_dynwind_block_asyncs}. When @var{mutex} is false, a recursive
2567692a
MV
624mutex provided by Guile is used instead.
625
661ae7ab
MV
626The effect of a call to @code{scm_dynwind_critical_section} is that
627the current dynwind context (@pxref{Dynamic Wind}) turns into a
628critical section. Because of the locked mutex, no second thread can
629enter it concurrently and because of the blocked asyncs, no system
630async can reenter it from the current thread.
2567692a
MV
631
632When the current thread reenters the critical section anyway, the kind
633of @var{mutex} determines what happens: When @var{mutex} is recursive,
634the reentry is allowed. When it is a normal mutex, an error is
635signalled.
636@end deftypefn
637
638
b4fddbbe
MV
639@node Fluids and Dynamic States
640@subsection Fluids and Dynamic States
07d83abe
MV
641
642@cindex fluids
643
b4fddbbe
MV
644A @emph{fluid} is an object that can store one value per @emph{dynamic
645state}. Each thread has a current dynamic state, and when accessing a
646fluid, this current dynamic state is used to provide the actual value.
647In this way, fluids can be used for thread local storage, but they are
648in fact more flexible: dynamic states are objects of their own and can
649be made current for more than one thread at the same time, or only be
650made current temporarily, for example.
651
652Fluids can also be used to simulate the desirable effects of
653dynamically scoped variables. Dynamically scoped variables are useful
654when you want to set a variable to a value during some dynamic extent
655in the execution of your program and have them revert to their
656original value when the control flow is outside of this dynamic
657extent. See the description of @code{with-fluids} below for details.
07d83abe
MV
658
659New fluids are created with @code{make-fluid} and @code{fluid?} is
660used for testing whether an object is actually a fluid. The values
661stored in a fluid can be accessed with @code{fluid-ref} and
662@code{fluid-set!}.
663
664@deffn {Scheme Procedure} make-fluid
665@deffnx {C Function} scm_make_fluid ()
666Return a newly created fluid.
b4fddbbe
MV
667Fluids are objects that can hold one
668value per dynamic state. That is, modifications to this value are
669only visible to code that executes with the same dynamic state as
670the modifying code. When a new dynamic state is constructed, it
671inherits the values from its parent. Because each thread normally executes
672with its own dynamic state, you can use fluids for thread local storage.
07d83abe
MV
673@end deffn
674
675@deffn {Scheme Procedure} fluid? obj
676@deffnx {C Function} scm_fluid_p (obj)
677Return @code{#t} iff @var{obj} is a fluid; otherwise, return
678@code{#f}.
679@end deffn
680
681@deffn {Scheme Procedure} fluid-ref fluid
682@deffnx {C Function} scm_fluid_ref (fluid)
683Return the value associated with @var{fluid} in the current
684dynamic root. If @var{fluid} has not been set, then return
685@code{#f}.
686@end deffn
687
688@deffn {Scheme Procedure} fluid-set! fluid value
689@deffnx {C Function} scm_fluid_set_x (fluid, value)
690Set the value associated with @var{fluid} in the current dynamic root.
691@end deffn
692
693@code{with-fluids*} temporarily changes the values of one or more fluids,
694so that the given procedure and each procedure called by it access the
695given values. After the procedure returns, the old values are restored.
696
cdf1ad3b
MV
697@deffn {Scheme Procedure} with-fluid* fluid value thunk
698@deffnx {C Function} scm_with_fluid (fluid, value, thunk)
699Set @var{fluid} to @var{value} temporarily, and call @var{thunk}.
700@var{thunk} must be a procedure with no argument.
701@end deffn
702
07d83abe
MV
703@deffn {Scheme Procedure} with-fluids* fluids values thunk
704@deffnx {C Function} scm_with_fluids (fluids, values, thunk)
705Set @var{fluids} to @var{values} temporary, and call @var{thunk}.
706@var{fluids} must be a list of fluids and @var{values} must be the
707same number of their values to be applied. Each substitution is done
708in the order given. @var{thunk} must be a procedure with no argument.
709it is called inside a @code{dynamic-wind} and the fluids are
710set/restored when control enter or leaves the established dynamic
711extent.
712@end deffn
713
714@deffn {Scheme Macro} with-fluids ((fluid value) ...) body...
715Execute @var{body...} while each @var{fluid} is set to the
716corresponding @var{value}. Both @var{fluid} and @var{value} are
717evaluated and @var{fluid} must yield a fluid. @var{body...} is
718executed inside a @code{dynamic-wind} and the fluids are set/restored
719when control enter or leaves the established dynamic extent.
720@end deffn
721
722@deftypefn {C Function} SCM scm_c_with_fluids (SCM fluids, SCM vals, SCM (*cproc)(void *), void *data)
723@deftypefnx {C Function} SCM scm_c_with_fluid (SCM fluid, SCM val, SCM (*cproc)(void *), void *data)
724The function @code{scm_c_with_fluids} is like @code{scm_with_fluids}
725except that it takes a C function to call instead of a Scheme thunk.
726
727The function @code{scm_c_with_fluid} is similar but only allows one
728fluid to be set instead of a list.
729@end deftypefn
730
661ae7ab 731@deftypefn {C Function} void scm_dynwind_fluid (SCM fluid, SCM val)
07d83abe 732This function must be used inside a pair of calls to
661ae7ab
MV
733@code{scm_dynwind_begin} and @code{scm_dynwind_end} (@pxref{Dynamic
734Wind}). During the dynwind context, the fluid @var{fluid} is set to
735@var{val}.
07d83abe
MV
736
737More precisely, the value of the fluid is swapped with a `backup'
661ae7ab
MV
738value whenever the dynwind context is entered or left. The backup
739value is initialized with the @var{val} argument.
07d83abe
MV
740@end deftypefn
741
b4fddbbe
MV
742@deffn {Scheme Procedure} make-dynamic-state [parent]
743@deffnx {C Function} scm_make_dynamic_state (parent)
744Return a copy of the dynamic state object @var{parent}
745or of the current dynamic state when @var{parent} is omitted.
746@end deffn
747
748@deffn {Scheme Procedure} dynamic-state? obj
749@deffnx {C Function} scm_dynamic_state_p (obj)
750Return @code{#t} if @var{obj} is a dynamic state object;
751return @code{#f} otherwise.
752@end deffn
753
754@deftypefn {C Procedure} int scm_is_dynamic_state (SCM obj)
755Return non-zero if @var{obj} is a dynamic state object;
756return zero otherwise.
757@end deftypefn
758
759@deffn {Scheme Procedure} current-dynamic-state
760@deffnx {C Function} scm_current_dynamic_state ()
761Return the current dynamic state object.
762@end deffn
763
764@deffn {Scheme Procedure} set-current-dynamic-state state
765@deffnx {C Function} scm_set_current_dynamic_state (state)
766Set the current dynamic state object to @var{state}
767and return the previous current dynamic state object.
768@end deffn
769
770@deffn {Scheme Procedure} with-dynamic-state state proc
771@deffnx {C Function} scm_with_dynamic_state (state, proc)
772Call @var{proc} while @var{state} is the current dynamic
773state object.
774@end deffn
775
661ae7ab
MV
776@deftypefn {C Procedure} void scm_dynwind_current_dynamic_state (SCM state)
777Set the current dynamic state to @var{state} for the current dynwind
778context.
b4fddbbe
MV
779@end deftypefn
780
c2110081 781@deftypefn {C Procedure} {void *} scm_c_with_dynamic_state (SCM state, void *(*func)(void *), void *data)
b4fddbbe
MV
782Like @code{scm_with_dynamic_state}, but call @var{func} with
783@var{data}.
784@end deftypefn
785
cc19cda7
MV
786@c @node Futures
787@c @subsection Futures
788@c @cindex futures
789
790@c -- Futures are disabled for the time being, see futures.h for an
791@c -- explanation.
792
793@c Futures are a convenient way to run a calculation in a new thread, and
794@c only wait for the result when it's actually needed.
795
796@c Futures are similar to promises (@pxref{Delayed Evaluation}), in that
797@c they allow mainline code to continue immediately. But @code{delay}
798@c doesn't evaluate at all until forced, whereas @code{future} starts
799@c immediately in a new thread.
800
801@c @deffn {syntax} future expr
802@c Begin evaluating @var{expr} in a new thread, and return a ``future''
803@c object representing the calculation.
804@c @end deffn
805
806@c @deffn {Scheme Procedure} make-future thunk
807@c @deffnx {C Function} scm_make_future (thunk)
808@c Begin evaluating the call @code{(@var{thunk})} in a new thread, and
809@c return a ``future'' object representing the calculation.
810@c @end deffn
811
812@c @deffn {Scheme Procedure} future-ref f
813@c @deffnx {C Function} scm_future_ref (f)
814@c Return the value computed by the future @var{f}. If @var{f} has not
815@c yet finished executing then wait for it to do so.
816@c @end deffn
07d83abe
MV
817
818
819@node Parallel Forms
820@subsection Parallel forms
821@cindex parallel forms
822
823The functions described in this section are available from
824
825@example
826(use-modules (ice-9 threads))
827@end example
828
829@deffn syntax parallel expr1 @dots{} exprN
af1323c5 830Evaluate each @var{expr} expression in parallel, each in its own thread.
07d83abe
MV
831Return the results as a set of @var{N} multiple values
832(@pxref{Multiple Values}).
833@end deffn
834
835@deffn syntax letpar ((var1 expr1) @dots{} (varN exprN)) body@dots{}
af1323c5 836Evaluate each @var{expr} in parallel, each in its own thread, then bind
07d83abe
MV
837the results to the corresponding @var{var} variables and evaluate
838@var{body}.
839
840@code{letpar} is like @code{let} (@pxref{Local Bindings}), but all the
841expressions for the bindings are evaluated in parallel.
842@end deffn
843
844@deffn {Scheme Procedure} par-map proc lst1 @dots{} lstN
845@deffnx {Scheme Procedure} par-for-each proc lst1 @dots{} lstN
846Call @var{proc} on the elements of the given lists. @code{par-map}
847returns a list comprising the return values from @var{proc}.
848@code{par-for-each} returns an unspecified value, but waits for all
849calls to complete.
850
851The @var{proc} calls are @code{(@var{proc} @var{elem1} @dots{}
852@var{elemN})}, where each @var{elem} is from the corresponding
853@var{lst}. Each @var{lst} must be the same length. The calls are
af1323c5 854made in parallel, each in its own thread.
07d83abe
MV
855
856These functions are like @code{map} and @code{for-each} (@pxref{List
857Mapping}), but make their @var{proc} calls in parallel.
858@end deffn
859
860@deffn {Scheme Procedure} n-par-map n proc lst1 @dots{} lstN
861@deffnx {Scheme Procedure} n-par-for-each n proc lst1 @dots{} lstN
862Call @var{proc} on the elements of the given lists, in the same way as
863@code{par-map} and @code{par-for-each} above, but use no more than
af1323c5 864@var{n} threads at any one time. The order in which calls are
07d83abe
MV
865initiated within that threads limit is unspecified.
866
867These functions are good for controlling resource consumption if
868@var{proc} calls might be costly, or if there are many to be made. On
869a dual-CPU system for instance @math{@var{n}=4} might be enough to
870keep the CPUs utilized, and not consume too much memory.
871@end deffn
872
873@deffn {Scheme Procedure} n-for-each-par-map n sproc pproc lst1 @dots{} lstN
874Apply @var{pproc} to the elements of the given lists, and apply
875@var{sproc} to each result returned by @var{pproc}. The final return
876value is unspecified, but all calls will have been completed before
877returning.
878
879The calls made are @code{(@var{sproc} (@var{pproc} @var{elem1} @dots{}
880@var{elemN}))}, where each @var{elem} is from the corresponding
881@var{lst}. Each @var{lst} must have the same number of elements.
882
af1323c5
KR
883The @var{pproc} calls are made in parallel, in separate threads. No more
884than @var{n} threads are used at any one time. The order in which
07d83abe
MV
885@var{pproc} calls are initiated within that limit is unspecified.
886
887The @var{sproc} calls are made serially, in list element order, one at
888a time. @var{pproc} calls on later elements may execute in parallel
889with the @var{sproc} calls. Exactly which thread makes each
890@var{sproc} call is unspecified.
891
892This function is designed for individual calculations that can be done
893in parallel, but with results needing to be handled serially, for
894instance to write them to a file. The @var{n} limit on threads
895controls system resource usage when there are many calculations or
896when they might be costly.
897
898It will be seen that @code{n-for-each-par-map} is like a combination
899of @code{n-par-map} and @code{for-each},
900
901@example
af1323c5 902(for-each sproc (n-par-map n pproc lst1 ... lstN))
07d83abe
MV
903@end example
904
905@noindent
906But the actual implementation is more efficient since each @var{sproc}
907call, in turn, can be initiated once the relevant @var{pproc} call has
908completed, it doesn't need to wait for all to finish.
909@end deffn
910
911
3cf066df 912
07d83abe
MV
913@c Local Variables:
914@c TeX-master: "guile.texi"
915@c End: