1:- module(resource_bounds, 2 [ resource_bounded_call/4 % resource_bounded_call(:Goal, +MaxCPU, 3 % -Status, +Options) 4 ]). 5:- use_module(library(option)). 6:- use_module(library(debug)). 7 8:- meta_predicate 9 resource_bounded_call( , , , ).
If all solutions of Goal are needed, Goal must be wrapped in findall/3.
Below are some examples
?- resource_bounded_call(true, 1, Status, []). Status = true. ?- resource_bounded_call(fail, 1, Status, []). Status = false. ?- resource_bounded_call((repeat, fail), 0.001, Status, []). Status = timeout(cpu). ?- resource_bounded_call(sleep(20), 0.001, Status, [wall_time(1)]). Status = timeout(wall). ?- resource_bounded_call(numlist(1, 1000000, L), 1, Status, [global(1000)]). Status = stack_overflow(global).
69resource_bounded_call(Goal, MaxTime, Status, Options) :- 70 queue_options(Options, QueueOpts), 71 thread_options(Options, ThreadOpts), 72 thread_self(Self), 73 term_variables(Goal, Vars), 74 thread_create(run(Goal, Vars, Self, Id), Id, ThreadOpts), 75 monitor_thread(Goal, Vars, Id, MaxTime, 0, QueueOpts, StatusVar), 76 Status = StatusVar. 77 78run(Goal, Vars, Main, Me) :- 79 call_cleanup(Goal, thread_send_message(Main, done(Me, Vars))). 80 81queue_options(Options, QueueOpts) :- 82 option(wall_time(Time), Options), !, 83 get_time(Now), 84 Deadline is Time+Now, 85 QueueOpts = [deadline(Deadline)]. 86queue_options(_, []). 87 88thread_options([], []). 89thread_options([H0|T0], [H|T]) :- 90 thread_option(H0, H), !, 91 thread_options(T0, T). 92thread_options([_|T0], T) :- 93 thread_options(T0, T). 94 95thread_option(local(Cells), local(KB)) :- 96 cells_kb(Cells, KB). 97thread_option(global(Cells), global(KB)) :- 98 cells_kb(Cells, KB). 99 100cells_kb(KCells, KB) :- 101 must_be(nonneg, KCells), 102 current_prolog_flag(address_bits, Bits), 103 KB is KCells * Bits//8. 104 105monitor_thread(Goal, Vars, Id, MaxTime, UsedTime, QueueOpts, Status) :- 106 thread_self(Self), 107 Left is MaxTime-UsedTime, 108 ( thread_get_message(Self, done(Id, Vars), 109 [ timeout(Left) 110 | QueueOpts 111 ]) 112 -> debug(monitor, 'Done ~w', [Id]), 113 thread_join(Id, Status0), 114 map_status(Status0, Status) 115 ; thread_statistics(Id, cputime, CPU), 116 ( ( CPU > MaxTime 117 -> Status = timeout(cpu) 118 ; QueueOpts = [deadline(Deadline)], 119 get_time(Now), 120 Now > Deadline 121 -> Status = timeout(wall) 122 ) 123 -> debug(monitor, 'Signalling ~w with abort', [Id]), 124 thread_signal(Id, abort), 125 debug(monitor, 'Waiting', []), 126 thread_join(Id, _), 127 thread_get_message(done(Id, _)), 128 debug(monitor, 'Joined', []) 129 ; monitor_thread(Goal, Vars, Id, MaxTime, CPU, QueueOpts, Status) 130 ) 131 ). 132 133map_status(exception(error(resource_error(stack), Stack)), 134 stack_overflow(Stack)) :- !. 135map_status(Status, Status)
Resource bounded execution of a goal
This library allows running a goal, providing limits for the wall time, CPU time and stack usage.