fix undefined virtual_alarm

This commit is contained in:
Vitor Santos Costa 2009-06-01 21:30:56 -05:00
parent 662dcde178
commit 217afd3a72
2 changed files with 23 additions and 6 deletions

View File

@ -14,7 +14,8 @@
stack_dump/0, stack_dump/0,
stack_dump/1, stack_dump/1,
enable_interrupts/0, enable_interrupts/0,
disable_interrupts/0 disable_interrupts/0,
virtual_alarm/3
]). ]).
stack_dump :- stack_dump :-
@ -35,5 +36,16 @@ run_formats([Com-Args|StackInfo], Stream) :-
format(Stream, Com, Args), format(Stream, Com, Args),
run_formats(StackInfo, user_error). run_formats(StackInfo, user_error).
virtual_alarm(Interval, Goal, Left) :-
Interval == 0, !,
virtual_alarm(0, 0, Left0, _),
on_signal(sig_alarm, _, Goal),
Left = Left0.
virtual_alarm(Interval, Goal, Left) :-
integer(Interval), !,
on_signal(sig_alarm, _, Goal),
alarm(Interval, 0, Left, _).
virtual_alarm(Interval.USecs, Goal, Left.LUSecs) :-
on_signal(sig_alarm, _, Goal),
virtual_alarm(Interval, USecs, Left, LUSecs).

View File

@ -21,6 +21,11 @@
:- meta_predicate time_out(:,+,-). :- meta_predicate time_out(:,+,-).
:- use_module(library(hacks), [
virtual_alarm/3
]).
% %
% not the nicest program I've ever seen. % not the nicest program I've ever seen.
% %
@ -30,15 +35,15 @@ time_out(Goal, Time, Result) :-
UT is (Time mod 1000)*1000, UT is (Time mod 1000)*1000,
catch( ( Result0 = success, catch( ( Result0 = success,
setup_call_cleanup( setup_call_cleanup(
yap_hacks:virtual_alarm(T.UT,throw(time_out),_), virtual_alarm(T.UT,throw(time_out),_),
Goal, Goal,
yap_hacks:virtual_alarm(0,_,RT)), virtual_alarm(0,_,RT)),
( var(RT) ( var(RT)
-> yap_hacks:virtual_alarm(0,_,_), -> virtual_alarm(0,_,_),
( (
true true
; ;
yap_hacks:virtual_alarm(T.UT,throw(time_out),_), virtual_alarm(T.UT,throw(time_out),_),
fail fail
) )
; true ; true