view qutils.pl @ 15:c91d53b19dbb tip

Meh?
author samer
date Wed, 19 Dec 2012 19:16:30 +0000
parents 44417282afec 02d99048fb78
children
line wrap: on
line source
:- module( qutils, 
		[	get_message_or_timeout/2
		,	send_with_size_limit/3
		]).

:- meta_predicate with_message(?,0).
:- meta_predicate with_message_or_timeout(+,?,0,0).

:- use_module(library(time)).
:- use_module(library(debug)).

% Older versions of SWI do not have alarm_at/3
:- if(\+current_predicate(alarm_at/3)).
%:- writeln('% Expanding alarm_at/3 to alarm_at/4.').
user:goal_expansion(alarm_at(A,B,C), alarm_at(A,B,C,[])).
:- endif.

%% get_message_or_timeout( +TimeOut, -Msg) is det.
%
%  Time-limited wait for next term in message queue.
%  Waits up to TimeOut seconds for the next message that 
%  unifies with Msg in the current thread.  If none arrives, 
%  then Msg is unified  with timeout. 
%  NB: may fail if Msg is bound on input.
get_message_or_timeout(inf,Msg) :- !, thread_get_message(Msg).

% Older versions of SWI do not have thread_get_message/3
:- if(current_predicate(thread_get_message/3)).

% we have thread_get_message/3 but we may or may not have the deadline/1 option
:- if(current_predicate_option(thread_get_message/3,3,deadline(_))).

%:- writeln('% compiling get_message_or_timeout/2 using deadline/1 option.').

:- if((current_prolog_flag(version,Version),Version<60102)).

get_message_or_timeout(Deadline,Msg) :- 
	thread_self(Thread),
	(	thread_get_message(Thread,Msg,[deadline(Deadline)]) 
	->	debug(qutils,'got message: ~w.',[Msg])
	;	Msg=timeout).

	%	(	get_time(Now), Now<Deadline
	%	->	thread_self(Thread),
	%		thread_get_message(Thread,Msg,[deadline(Deadline)]),
	%		debug(qutils,'got message: ~w.',[Msg])
	%	;	Msg=timeout
	%	).

:- else.

get_message_or_timeout(Deadline,Msg) :- 
	thread_self(Thread),
	(	thread_get_message(Thread,Msg,[deadline(Deadline)])
	->	debug(qutils,'got message: ~w.',[Msg])
	;	Msg=timeout
	).

:- endif.

:- else.

%:- writeln('% compiling get_message_or_timeout/2 using timeout/1 option.').
get_message_or_timeout(Deadline,Msg) :- 
	get_time(Now), 
	(	Now>=Deadline 
	-> Msg=timeout, 
		debug(qutils,'deadline already missed.',[])
	;	Timeout is Deadline-Now,
		thread_self(Thread),
		thread_get_message(Thread,Msg,[timeout(Timeout)]),
		debug(qutils,'got message: ~w.',[Msg])
	).	
:- endif.

:- else.

%:- writeln('% compiling get_message_or_timeout/2 using alarm and message send.').
get_message_or_timeout(Deadline,Msg) :- 
	get_time(Now), 
	(	Now>=Deadline 
	-> Msg=timeout,
		debug(qutils,'deadline already missed.',[])
	;	thread_self(Thread),
		setup_call_cleanup(
			alarm_at(Deadline, thread_send_message(Thread,timeout), Id), 
			thread_get_message(Thread,Msg),
			time:remove_alarm_notrace(Id)),
		debug(qutils,'got message: ~w.',[Msg])
	).	

:-endif.

%% send_with_size_limit( +Max:natural, +Queue:queue_id, +Msg:term) is det.
%
%  Adds term to message queue unless queue is already full.
%  If message queue Queu already contains more than Max elements,
%  then "*" is printed and the procedure succeeds. NB. the message
%  is discarded.
send_with_size_limit(Max,Queue,Msg) :-
	message_queue_property(Queue,size(QSize)),
	(	QSize<Max -> thread_send_message(Queue,Msg)
	;	writeln('*')
	).