1/* Part of SWI-Prolog 2 3 Author: Jan Wielemaker 4 E-mail: J.Wielemaker@vu.nl 5 WWW: http://www.swi-prolog.org 6 Copyright (c) 2007-2018, University of Amsterdam 7 VU University Amsterdam 8 All rights reserved. 9 10 Redistribution and use in source and binary forms, with or without 11 modification, are permitted provided that the following conditions 12 are met: 13 14 1. Redistributions of source code must retain the above copyright 15 notice, this list of conditions and the following disclaimer. 16 17 2. Redistributions in binary form must reproduce the above copyright 18 notice, this list of conditions and the following disclaimer in 19 the documentation and/or other materials provided with the 20 distribution. 21 22 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 23 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 24 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 25 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 26 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 27 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 28 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 29 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 30 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 31 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 32 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 33 POSSIBILITY OF SUCH DAMAGE. 34*/ 35 36:- module(thread, 37 [ concurrent/3, % +Threads, :Goals, +Options 38 concurrent_maplist/2, % :Goal, +List 39 concurrent_maplist/3, % :Goal, ?List1, ?List2 40 concurrent_maplist/4, % :Goal, ?List1, ?List2, ?List3 41 first_solution/3 % -Var, :Goals, +Options 42 ]). 43:- use_module(library(debug)). 44:- use_module(library(error)). 45:- use_module(library(lists)). 46:- use_module(library(apply)). 47:- use_module(library(option)). 48 49%:- debug(concurrent). 50 51:- meta_predicate 52 concurrent( , , ), 53 concurrent_maplist( , ), 54 concurrent_maplist( , , ), 55 concurrent_maplist( , , , ), 56 first_solution( , , ). 57 58:- predicate_options(concurrent/3, 3, 59 [ pass_to(system:thread_create/3, 3) 60 ]). 61:- predicate_options(first_solution/3, 3, 62 [ on_fail(oneof([stop,continue])), 63 on_error(oneof([stop,continue])), 64 pass_to(system:thread_create/3, 3) 65 ]).
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:
144concurrent(1, M:List, _) :- 145 !, 146 maplist(once_in_module(M), List). 147concurrent(N, M:List, Options) :- 148 must_be(positive_integer, N), 149 must_be(list(callable), List), 150 length(List, JobCount), 151 message_queue_create(Done), 152 message_queue_create(Queue), 153 WorkerCount is min(N, JobCount), 154 create_workers(WorkerCount, Queue, Done, Workers, Options), 155 submit_goals(List, 1, M, Queue, VarList), 156 forall(between(1, WorkerCount, _), 157 thread_send_message(Queue, done)), 158 VT =.. [vars|VarList], 159 concur_wait(JobCount, Done, VT, cleanup(Workers, Queue), 160 Result, [], Exitted), 161 subtract(Workers, Exitted, RemainingWorkers), 162 concur_cleanup(Result, RemainingWorkers, [Queue, Done]), 163 ( Result == true 164 -> true 165 ; Result = false 166 -> fail 167 ; Result = exception(Error) 168 -> throw(Error) 169 ). 170 171once_in_module(M, Goal) :- 172 call(M:Goal), !.
goal(Id, Goal, Vars)
. Vars is unified with a list of
lists of free variables appearing in each goal.180submit_goals([], _, _, _, []). 181submit_goals([H|T], I, M, Queue, [Vars|VT]) :- 182 term_variables(H, Vars), 183 thread_send_message(Queue, goal(I, M:H, Vars)), 184 I2 is I + 1, 185 submit_goals(T, I2, M, Queue, VT).
196concur_wait(0, _, _, _, true, Exited, Exited) :- !. 197concur_wait(N, Done, VT, Cleanup, Status, Exitted0, Exitted) :- 198 debug(concurrent, 'Concurrent: waiting for workers ...', []), 199 catch(thread_get_message(Done, Exit), Error, 200 concur_abort(Error, Cleanup, Done, Exitted0)), 201 debug(concurrent, 'Waiting: received ~p', [Exit]), 202 ( Exit = done(Id, Vars) 203 -> debug(concurrent, 'Concurrent: Job ~p completed with ~p', [Id, Vars]), 204 arg(Id, VT, Vars), 205 N2 is N - 1, 206 concur_wait(N2, Done, VT, Cleanup, Status, Exitted0, Exitted) 207 ; Exit = finished(Thread) 208 -> thread_join(Thread, JoinStatus), 209 debug(concurrent, 'Concurrent: waiter ~p joined: ~p', 210 [Thread, JoinStatus]), 211 ( JoinStatus == true 212 -> concur_wait(N, Done, VT, Cleanup, Status, [Thread|Exitted0], Exitted) 213 ; Status = JoinStatus, 214 Exitted = [Thread|Exitted0] 215 ) 216 ). 217 218concur_abort(Error, cleanup(Workers, Queue), Done, Exitted) :- 219 debug(concurrent, 'Concurrent: got ~p', [Error]), 220 subtract(Workers, Exitted, RemainingWorkers), 221 concur_cleanup(Error, RemainingWorkers, [Queue, Done]), 222 throw(Error). 223 224create_workers(N, Queue, Done, [Id|Ids], Options) :- 225 N > 0, 226 !, 227 thread_create(worker(Queue, Done), Id, 228 [ at_exit(thread_send_message(Done, finished(Id))) 229 | Options 230 ]), 231 N2 is N - 1, 232 create_workers(N2, Queue, Done, Ids, Options). 233create_workers(_, _, _, [], _).
240worker(Queue, Done) :-
241 thread_get_message(Queue, Message),
242 debug(concurrent, 'Worker: received ~p', [Message]),
243 ( Message = goal(Id, Goal, Vars)
244 -> (
245 -> thread_send_message(Done, done(Id, Vars)),
246 worker(Queue, Done)
247 )
248 ; true
249 ).
true
, signal all workers to make them stop prematurely. If
result is true we assume all workers have been instructed to
stop or have stopped themselves.259concur_cleanup(Result, Workers, Queues) :- 260 !, 261 ( Result == true 262 -> true 263 ; kill_workers(Workers) 264 ), 265 join_all(Workers), 266 maplist(message_queue_destroy, Queues). 267 268kill_workers([]). 269kill_workers([Id|T]) :- 270 debug(concurrent, 'Signalling ~w', [Id]), 271 catch(thread_signal(Id, abort), _, true), 272 kill_workers(T). 273 274join_all([]). 275join_all([Id|T]) :- 276 thread_join(Id, _), 277 join_all(T). 278 279 280 /******************************* 281 * MAPLIST * 282 *******************************/
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.
301concurrent_maplist(Goal, List) :- 302 workers(List, WorkerCount), 303 !, 304 maplist(ml_goal(Goal), List, Goals), 305 concurrent(WorkerCount, Goals, []). 306concurrent_maplist(M:Goal, List) :- 307 maplist(once_in_module(M, Goal), List). 308 309once_in_module(M, Goal, Arg) :- 310 call(M:Goal, Arg), !. 311 312ml_goal(Goal, Elem, call(Goal, Elem)). 313 314concurrent_maplist(Goal, List1, List2) :- 315 same_length(List1, List2), 316 workers(List1, WorkerCount), 317 !, 318 maplist(ml_goal(Goal), List1, List2, Goals), 319 concurrent(WorkerCount, Goals, []). 320concurrent_maplist(M:Goal, List1, List2) :- 321 maplist(once_in_module(M, Goal), List1, List2). 322 323once_in_module(M, Goal, Arg1, Arg2) :- 324 call(M:Goal, Arg1, Arg2), !. 325 326ml_goal(Goal, Elem1, Elem2, call(Goal, Elem1, Elem2)). 327 328concurrent_maplist(Goal, List1, List2, List3) :- 329 same_length(List1, List2, List3), 330 workers(List1, WorkerCount), 331 !, 332 maplist(ml_goal(Goal), List1, List2, List3, Goals), 333 concurrent(WorkerCount, Goals, []). 334concurrent_maplist(M:Goal, List1, List2, List3) :- 335 maplist(once_in_module(M, Goal), List1, List2, List3). 336 337once_in_module(M, Goal, Arg1, Arg2, Arg3) :- 338 call(M:Goal, Arg1, Arg2, Arg3), !. 339 340ml_goal(Goal, Elem1, Elem2, Elem3, call(Goal, Elem1, Elem2, Elem3)). 341 342workers(List, Count) :- 343 current_prolog_flag(cpu_count, Cores), 344 Cores > 1, 345 length(List, Len), 346 Count is min(Cores,Len), 347 Count > 1, 348 !. 349 350same_length([], [], []). 351same_length([_|T1], [_|T2], [_|T3]) :- 352 same_length(T1, T2, T3). 353 354 355 /******************************* 356 * FIRST * 357 *******************************/
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.
stop
(default), terminate all threads and stop with
the failure. If continue
, keep waiting.397first_solution(X, M:List, Options) :- 398 message_queue_create(Done), 399 thread_options(Options, ThreadOptions, RestOptions), 400 length(List, JobCount), 401 create_solvers(List, M, X, Done, Solvers, ThreadOptions), 402 wait_for_one(JobCount, Done, Result, RestOptions), 403 concur_cleanup(kill, Solvers, [Done]), 404 ( Result = done(_, Var) 405 -> X = Var 406 ; Result = error(_, Error) 407 -> throw(Error) 408 ). 409 410create_solvers([], _, _, _, [], _). 411create_solvers([H|T], M, X, Done, [Id|IDs], Options) :- 412 thread_create(solve(M:H, X, Done), Id, Options), 413 create_solvers(T, M, X, Done, IDs, Options). 414 415solve(Goal, Var, Queue) :- 416 thread_self(Me), 417 ( catch(Goal, E, true) 418 -> ( var(E) 419 -> thread_send_message(Queue, done(Me, Var)) 420 ; thread_send_message(Queue, error(Me, E)) 421 ) 422 ; thread_send_message(Queue, failed(Me)) 423 ). 424 425wait_for_one(0, _, failed, _) :- !. 426wait_for_one(JobCount, Queue, Result, Options) :- 427 thread_get_message(Queue, Msg), 428 LeftCount is JobCount - 1, 429 ( Msg = done(_, _) 430 -> Result = Msg 431 ; Msg = failed(_) 432 -> ( option(on_fail(stop), Options, stop) 433 -> Result = Msg 434 ; wait_for_one(LeftCount, Queue, Result, Options) 435 ) 436 ; Msg = error(_, _) 437 -> ( option(on_error(stop), Options, stop) 438 -> Result = Msg 439 ; wait_for_one(LeftCount, Queue, Result, Options) 440 ) 441 ).
thread(-size)
options and other
options.449thread_options([], [], []). 450thread_options([H|T], [H|Th], O) :- 451 thread_option(H), 452 !, 453 thread_options(T, Th, O). 454thread_options([H|T], Th, [H|O]) :- 455 thread_options(T, Th, O). 456 457thread_option(local(_)). 458thread_option(global(_)). 459thread_option(trail(_)). 460thread_option(argument(_)). 461thread_option(stack(_))
High level thread primitives
This module defines simple to use predicates for running goals concurrently. Where the core multi-threaded API is targeted at communicating long-living threads, the predicates here are defined to run goals concurrently without having to deal with thread creation and maintenance explicitely.
Note that these predicates run goals concurrently and therefore these goals need to be thread-safe. As the predicates in this module also abort branches of the computation that are no longer needed, predicates that have side-effect must act properly. In a nutshell, this has the following consequences: