File:  [Public] / 2004 / semwalker / bench.pl
Revision 1.12: download - view: text, annotated - select for diffs
Mon Oct 11 20:41:09 2004 UTC (21 years, 1 month ago) by sandro
Branches: MAIN
CVS tags: before_oct_2006_restructuring, HEAD
added some rdf

/* General utility for measuring how fast bits of code run, with much
more precision than time/1, because it repeats them many times.  So
it's best for very quick thinks.  :-) */

:- ensure_loaded(library(debug)).
:- debug(timestamp).
:- ensure_loaded(library('semweb/rdf_db')).


timestamp(Label) :-
	get_time(New),
	flag(timestamp, Old, New),
	Diff is New - Old,
	debug(timestamp, 'elapsed time: ~a seconds, at ~q', [Diff, Label]).

time_n(Goal, Time, N) :-
   get_time(T), 
   (  between(1,N,_), 
      once(Goal), 
      fail
   ; true), 
   get_time(T2), 
   Time is (T2-T)/N.


bench(Goal) :-
	(   between(1,6,Y),
	    time_n(fail, Base, 100),
	    time_n(Goal, T, 100),
	    Diff is (T - Base) * 1000000,
	    format('Run ~a: ~fus~n', [Y,Diff]), 
	    fail
	;   true
	).

benchline1(Goal, Reps, Diff) :-
	time_n(fail, Base, Reps),
	time_n(Goal, Time, Reps),
	Diff is Time - Base.

benchline(Goal, Reps, Median) :-
	findall(Time,
		(   between(1,5,_),
		    benchline1(Goal, Reps, Time)
		),
		Times),
	sort(Times, SortedTimes),
	SortedTimes = [_, _, Median, _, _],
	!.

sample(true).
sample(x=x).
sample(x\=y).
sample(f_true).
sample(f_f_true).
sample(f_f_f_true).
sample(_ is 1+1).
sample(_ is 1000*1000).
sample(_ is 10^5).
sample(atom_concat(a,b,_)).
sample(atom_number('1', _)).
sample(atom_number(_, 1)).
sample(atom_number('1', 1)).
sample(term_to_atom(x, _)).
sample(term_to_atom(_, x)).
sample(term_to_atom(x, x)).
sample(term_to_atom(some(fairly(complex, [1,2,3,4]), term), _)).
sample(term_to_atom(_, 'some(fairly(complex, [1,2,3,4]), term)')).
sample(get_time(_)).
sample(mutex_lock(m)).
sample(mutex_unlock(m)).
sample((mutex_lock(m2), mutex_unlock(m2))).
sample(with_mutex(m3, true)).
sample(mutex_create(_)).
sample((mutex_create(X), mutex_lock(X))).
sample(call(true)).
sample(call_cleanup(true, true)).
sample(catch(true, _, true)).
sample(thread_send_message(main, hello)).
sample(thread_get_message(main, hello)).
sample(b_setval(foo, bar)).
sample(nb_setval(foo, bar)).
sample(flag(foo, _, bar)).
sample(flag(counter, N, N+1)).
sample((assert(foo(bar), R), erase(R))).
sample(assert(foo1(bin))).
sample(retract(foo1(bin))).
sample((assert(foo2(baz)), retract(foo2(baz)))).
sample(assert(foo3(buz))).
sample(asserta(foo6(buz))).
sample(assertz(foo7(buz))).
sample(retractall(foo3(buz))).
sample((recorda(foo, bar, R), erase(R))).
sample((X=foo4(baz), setarg(1, X, bar))).
sample(rdf(not, found, in, rdf_db)).
sample(rdf_assert(yes, found, in, rdf_db)).
sample(rdf(yes, found, in, rdf_db)).

f_true :- true.
f_f_true :- f_true.
f_f_f_true :- f_f_true.


bench_report :-
	findall([Time, Goal],
	     (   sample(Goal),
		 benchline(Goal, 10000, Time)
	     ),
	     Times),
	sort(Times, Sorted),
	format('  Unsorted~n'),
	forall(   member([Time, Goal], Times),
		  (   USec is Time * 1000000,
		      format('~t~q ~65| ~t~f usec~n', [Goal, USec])
		  )
	      ),
	format('  Sorted by Time~n'),
	forall(   member([Time, Goal], Sorted),
		  (   USec is Time * 1000000,
		      format('~t~q ~65| ~t~1f usec~n', [Goal, USec])
		  )
	      ).



Webmaster