Extends support for threads in the SWI-Prolog standard library.
- create_detached_thread(:Goal_0) is det
- create_detached_thread(+Alias:atom, :Goal_0) is det
- thread_list is det
- thread_name(+Id:handle, -Alias:atom) is det
- thread_self_property(+Property:compound) is semidet
- thread_self_property(-Property:compound) is multi
- threaded_maplist_1(:Goal_1, ?Args1:list) is det
- threaded_maplist_1(+N:positive_integer, :Goal_1, ?Args1:list) is det
- threaded_maplist_2(:Goal_2, ?Args1:list, ?Args2:list) is det
- threaded_maplist_2(+N:positive_integer, :Goal_2, ?Args1:list, ?Args2:list) is det
Re-exported predicates
The following predicates are exported from this file while their implementation is defined in imported modules or non-module files loaded by this module.
- concurrent(+N, :Goals, +Options) is semidet
- Run Goals in parallel using N threads. This call blocks until
all work has been done. The Goals must be independent. They
should not communicate using shared variables or any form of
global data. All Goals must be thread-safe.
Execution succeeds if all goals have succeeded. If one goal
fails or throws an exception, other workers are abandoned as
soon as possible and the entire computation fails or re-throws
the exception. Note that if multiple goals fail or raise an
error it is not defined which error or failure is reported.
On successful completion, variable bindings are returned. Note
however that threads have independent stacks and therefore the
goal is copied to the worker thread and the result is copied
back to the caller of concurrent/3.
Choosing the right number of threads is not always obvious. Here
are some scenarios:
- If the goals are CPU intensive and normally all succeeding,
typically the number of CPUs is the optimal number of
threads. Less does not use all CPUs, more wastes time in
context switches and also uses more memory.
- If the tasks are I/O bound the number of threads is
typically higher than the number of CPUs.
- If one or more of the goals may fail or produce an error,
using a higher number of threads may find this earlier.
- Arguments:
-
N | - Number of worker-threads to create. Using 1, no threads
are created. If N is larger than the number of Goals we
create exactly as many threads as there are Goals. |
Goals | - List of callable terms. |
Options | - Passed to thread_create/3 for creating the
workers. Only options changing the stack-sizes can
be used. In particular, do not pass the detached or alias
options. |
- See also
- - In many cases, concurrent_maplist/2 and friends
is easier to program and is tractable to program
analysis.
- concurrent_forall(:Generate, :Action) is semidet
- concurrent_forall(:Generate, :Action, +Options) is semidet
- True when Action is true for all solutions of Generate. This has the
same semantics as forall/2, but the Action goals are executed in
multiple threads. Notable a failing Action or a Action throwing an
exception signals the calling thread which in turn aborts all
workers and fails or re-throws the generated error. Options:
- threads(+Count)
- Number of threads to use. The default is determined by the
Prolog flag
cpu_count
.
- To be done
- - Ideally we would grow the set of workers dynamically, similar
to dynamic scheduling of HTTP worker threads. This would avoid
creating threads that are never used if Generate is too slow or does
not provide enough answers and would further raise the number of
threads if Action is I/O bound rather than CPU bound.
- concurrent_forall(:Generate, :Action) is semidet
- concurrent_forall(:Generate, :Action, +Options) is semidet
- True when Action is true for all solutions of Generate. This has the
same semantics as forall/2, but the Action goals are executed in
multiple threads. Notable a failing Action or a Action throwing an
exception signals the calling thread which in turn aborts all
workers and fails or re-throws the generated error. Options:
- threads(+Count)
- Number of threads to use. The default is determined by the
Prolog flag
cpu_count
.
- To be done
- - Ideally we would grow the set of workers dynamically, similar
to dynamic scheduling of HTTP worker threads. This would avoid
creating threads that are never used if Generate is too slow or does
not provide enough answers and would further raise the number of
threads if Action is I/O bound rather than CPU bound.
- concurrent_and(:Generator, :Test)
- concurrent_and(:Generator, :Test, +Options)
- Concurrent version of
(Generator,Test)
. This predicate creates a
thread providing solutions for Generator that are handed to a pool
of threads that run Test for the different instantiations provided
by Generator concurrently. The predicate is logically equivalent to
a simple conjunction except for two aspects: (1) terms are copied
from Generator to the test Test threads while answers are copied
back to the calling thread and (2) answers may be produced out of
order.
If the evaluation of some Test raises an exception,
concurrent_and/2,3 is terminated with this exception. If the caller
commits after a given answer or raises an exception while
concurrent_and/2,3 is active with pending choice points, all
involved resources are reclaimed.
Options:
- threads(+Count)
- Create a worker pool holding Count threads. The default is
the Prolog flag
cpu_count
.
This predicate was proposed by Jan Burse as
balance((Generator,Test))
.
- concurrent_and(:Generator, :Test)
- concurrent_and(:Generator, :Test, +Options)
- Concurrent version of
(Generator,Test)
. This predicate creates a
thread providing solutions for Generator that are handed to a pool
of threads that run Test for the different instantiations provided
by Generator concurrently. The predicate is logically equivalent to
a simple conjunction except for two aspects: (1) terms are copied
from Generator to the test Test threads while answers are copied
back to the calling thread and (2) answers may be produced out of
order.
If the evaluation of some Test raises an exception,
concurrent_and/2,3 is terminated with this exception. If the caller
commits after a given answer or raises an exception while
concurrent_and/2,3 is active with pending choice points, all
involved resources are reclaimed.
Options:
- threads(+Count)
- Create a worker pool holding Count threads. The default is
the Prolog flag
cpu_count
.
This predicate was proposed by Jan Burse as
balance((Generator,Test))
.
- concurrent_maplist(:Goal, +List) is semidet
- concurrent_maplist(:Goal, +List1, +List2) is semidet
- concurrent_maplist(:Goal, +List1, +List2, +List3) is semidet
- Concurrent version of maplist/2. This predicate uses concurrent/3,
using multiple worker threads. The number of threads is the
minimum of the list length and the number of cores available. The
number of cores is determined using the prolog flag
cpu_count
. If
this flag is absent or 1 or List has less than two elements, this
predicate calls the corresponding maplist/N version using a wrapper
based on once/1. Note that all goals are executed as if wrapped in
once/1 and therefore these predicates are semidet.
Note that the the overhead of this predicate is considerable and
therefore Goal must be fairly expensive before one reaches a
speedup.
- concurrent_maplist(:Goal, +List) is semidet
- concurrent_maplist(:Goal, +List1, +List2) is semidet
- concurrent_maplist(:Goal, +List1, +List2, +List3) is semidet
- Concurrent version of maplist/2. This predicate uses concurrent/3,
using multiple worker threads. The number of threads is the
minimum of the list length and the number of cores available. The
number of cores is determined using the prolog flag
cpu_count
. If
this flag is absent or 1 or List has less than two elements, this
predicate calls the corresponding maplist/N version using a wrapper
based on once/1. Note that all goals are executed as if wrapped in
once/1 and therefore these predicates are semidet.
Note that the the overhead of this predicate is considerable and
therefore Goal must be fairly expensive before one reaches a
speedup.
- concurrent_maplist(:Goal, +List) is semidet
- concurrent_maplist(:Goal, +List1, +List2) is semidet
- concurrent_maplist(:Goal, +List1, +List2, +List3) is semidet
- Concurrent version of maplist/2. This predicate uses concurrent/3,
using multiple worker threads. The number of threads is the
minimum of the list length and the number of cores available. The
number of cores is determined using the prolog flag
cpu_count
. If
this flag is absent or 1 or List has less than two elements, this
predicate calls the corresponding maplist/N version using a wrapper
based on once/1. Note that all goals are executed as if wrapped in
once/1 and therefore these predicates are semidet.
Note that the the overhead of this predicate is considerable and
therefore Goal must be fairly expensive before one reaches a
speedup.
- first_solution(-X, :Goals, +Options) is semidet
- Try alternative solvers concurrently, returning the first
answer. In a typical scenario, solving any of the goals in Goals
is satisfactory for the application to continue. As soon as one
of the tried alternatives is successful, all the others are
killed and first_solution/3 succeeds.
For example, if it is unclear whether it is better to search a
graph breadth-first or depth-first we can use:
search_graph(Grap, Path) :-
first_solution(Path, [ breadth_first(Graph, Path),
depth_first(Graph, Path)
],
[]).
Options include thread stack-sizes passed to thread_create, as
well as the options on_fail
and on_error
that specify what
to do if a solver fails or triggers an error. By default
execution of all solvers is terminated and the result is
returned. Sometimes one may wish to continue. One such scenario
is if one of the solvers may run out of resources or one of the
solvers is known to be incomplete.
- on_fail(Action)
- If
stop
(default), terminate all threads and stop with
the failure. If continue
, keep waiting.
- on_error(Action)
- As above, re-throwing the error if an error appears.
- bug
- - first_solution/3 cannot deal with non-determinism. There
is no obvious way to fit non-determinism into it. If multiple
solutions are needed wrap the solvers in findall/3.
- call_in_thread(+Thread, :Goal) is semidet
- Run Goal as an interrupt in the context of Thread. This is based on
thread_signal/2. If waiting times out, we inject a
stop(Reason)
exception into Goal. Interrupts can be nested, i.e., it is allowed
to run a call_in_thread/2 while the target thread is processing such
an interrupt.
This predicate is primarily intended for debugging and inspection
tasks.
Undocumented predicates
The following predicates are exported, but not or incorrectly documented.
- create_detached_thread(Arg1, Arg2)
- threaded_maplist_1(Arg1, Arg2, Arg3)
- threaded_maplist_2(Arg1, Arg2, Arg3)
- threaded_maplist_2(Arg1, Arg2, Arg3, Arg4)