view recorder.pl @ 12:24236c9c07b6

Added missing module import.
author samer
date Wed, 29 Feb 2012 20:30:31 +0000
parents 6beef97eda32
children
line wrap: on
line source
:- module(recorder, 
	[	recorder/2
	,	save_events/1
	,	load_events/1
	,	get_events/1
	,	player/2
	,	player/3
	]).
/** <module> event recording

This module provides a way to capture and record events processed by
the reactive programming framework of reactive.pl.
*/
:- meta_predicate recorder(1,?), player(1,?), player(2,2,?).
:- dynamic start_time/1, event/2.

:- use_module(library(fileutils)).
:- use_module(library(utils),[min/3]).
:- use_module(reactive).


%% recorder( +Client:ptail, -Proc:process) is det.
%
%  This predicate represents a reactive process that behaves as Client,
%  but records all events in the Prolog dynamic database. The type signature
%  implies that the term recorder(Client) is of type =|ptail|=. All previously
%  recorded events are deleted first. The time at which this predicate was
%  called is also recorded in the database. 

recorder(Client,Proc) :-
	get_time(Now),
	retractall(event(_,_)),
	retractall(start_time(_)),
	assert(start_time(Now)),
	format('recording events for ~w.\n',[Client]),
	call(Client,C1),
	recorder_cont(C1,Proc).

recorder_on_event(E,C1,Proc) :-
	assert(E),	
	step_event(E,C1,C2),
	recorder_cont(C2,Proc).

recorder_on_timeout(T,C1,Proc) :-
	step_timeout(T,C1,C2),
	recorder_cont(C2,Proc).

recorder_cont(C1,Proc) :-
	get_timeout(C1,T1),
	(	T1=inf
	->	req_message(E^recorder_on_event(E,C1), Proc)
	;	req_message_or_timeout(T1,
			recorder_on_timeout(T1,C1),
			E^recorder_on_event(E,C1), Proc)
	).

%% player( +Client:ptail, +Trans:pred(A,A), -Proc:process) is det.
%% player( +Client:ptail, -Proc:process) is det.
%
%  This predicate represents a reactive process that behaves as Client,
%  but plays back events in the Prolog dynamic database. The events are
%  time shifted by the difference between the recorded start time and the
%  time at which player/2 is called. The type signature
%  implies that the term recorder(Client) is of type =|ptail|=.
%
%  player/3 allows an event transformer pred(+EventIn:A,-EventOut:A) to be
%  specified. player/2 is equivalent to using=/2 as the transformer.

player(Client,Proc) :-
	get_time(Now), 
	start_time(T0), DT is Now-T0,
	setof(event(T,Msg),T1^(event(T1,Msg),T is DT+T1),Events),
	call(Client,C1),
	player_cont(Events,C1,Proc).

player(Client,Trans,Proc) :-
	get_time(Now), 
	start_time(T0), DT is Now-T0,
	setof(event(T,Msg),T1^Msg1^(event(T1,Msg1),T is DT+T1, call(Trans,Msg1,Msg)),Events),
	call(Client,C1),
	player_cont(Events,C1,Proc).

player_on_event(Events,C1,Proc) :-
	player_cont(Events,C1,Proc).

player_on_timeout(T,ET,Events,C1,Proc) :-
	(	T<ET 
	->	step_timeout(T,C1,C2),
		player_cont(Events,C2,Proc)
	;	Events=[E1|EX],
		step_event(E1,C1,C2),
		player_cont(EX,C2,Proc)
	).

player_cont([],C1,C1) :- !,
	writeln('Playback finished - continuing in interactive mode').

player_cont(Events,C1,Proc) :-
	Events=[event(ET,_)|_],
	get_timeout(C1,T1),
	min(ET,T1,TO),

	req_message_or_timeout(TO,
		player_on_timeout(TO,ET,Events,C1),
		_^player_on_event(Events,C1), Proc).


%% save_events(+FileName:atom) is det.
%  Save events in the event database to the named file (as Prolog clauses).
save_events(File) :- 
	with_output_to_file(File,(listing(start_time),listing(event))).


%% load_events(+FileName:atom) is det.
%  Load events from the named file to the event database, after removing
%  any events currently in there.
load_events(File) :-
	retractall(event(_,_)),
	retractall(start_time(_)),
	consult(File).


%% get_events(-Events:list(event)) is det.
%  Gets the currently loaded events as a list. Event times are relative
%  to start time.
get_events(Events) :-
	start_time(T0), 
	setof(event(T,Msg),T1^(event(T1,Msg),T is T1-T0),Events).