about(best,
	  	Max,  
		[max=Max, sum=Sum, nKeys=NKeys,yawns=Yawns
        ,minKey=Keys,betters=Betters,contents=Pairs
        ],
            best(Max,Sum,NKeys,Yawns,Keys,Betters,Pairs),
            best(Max,           % max number of best items to cache
					0,          % sum of the keys in the cache
					0,          % current number of keys on the buffer
					0,          % number of yawns
	                Default,    % minimum of keys seen so far.
					0,          % number of betters
					[]          % pairs of Key = Value, numeric  keys with value
                                % greater than -1*2^31, , sorted descending
				)) :- Max > 1, defaultMin(Default).

portray(best(Max,Sum,NKeys,Yawns,Keys,Betters,L)) :-
	length(L,N),
	write(best(Max,Sum,NKeys,Yawns,Keys,Betters,pairs/N)).

defaultMin( -2147483648). % -1*2^31

%%%% addition

best(Key=Val,Op,B0,B) :-
	interesting(Op,Key,B0),
    (Op = 0 -> yawn(B0,B) ; hooray(Key=Val,B0,B)).

interesting(2,Key,best(_  ,_,_    ,_,Min,_,_)) :- Key > Min,!.
interesting(1,_  ,best(Max,_,Size ,_,_  ,_,_)) :- Size < Max,!.
interesting(0,_  ,_).

yawn( best(A,B,C,Yawns0,D,E,F), 
      best(A,B,C,Yawns ,D,E,F)) :- Yawns is Yawns0 + 1.

hooray(Key=Val, best(Max,Sum0,Max,_,_,Adds,Pairs0),B) :- !,
    % special case: we are full. dump smallest before adding new
	almostLast(Pairs0,Almost=_,Last=_,Pairs),
	Sum  is Sum0 - Last,
	Size is Max - 1,
	hooray(Key=Val,best(Max,Sum ,Size,0,Almost,Adds,Pairs ),B).
hooray(Key=Val,    best(Max,Sum0,N0  ,_,Min0  ,Adds0,Pairs0),
                   best(Max,Sum, N   ,0,Min   ,Adds, Pairs )) :-
    % general case: add something new
	newKey(Min0,Key,Min),
	addDown(Pairs0,Key=Val,Pairs),
	Sum is Key + Sum0,
	Adds is Adds0 + 1,
	N  is N0 + 1.

newKey(X   ,Key,Key) :- defaultMin(X),!.
newKey(Min ,Key,Key) :- Key < Min,!.
newKey(Min,   _,Min).

almostLast([Almost,Last],Almost,Last,[Almost]).
almostLast([X,Y,Z|T0],Almost,Last,[X|T]) :- 
	almostLast([Y,Z|T0],Almost,Last,T).

%%%% selection
% sample key,values according to the "keys" distribution
any(best(_,Sum,_,_,Least,_,[Best=Thing|Rest]),K=V) :-
	R is random(32768)/32768,
	Range is Sum - Least,
	any1([Best=Thing|Rest],0,Range,R,Best=Thing,K=V).

any1([]       ,       _,  _  ,_   ,Last,Last).
any1([K=V | T],SumLeft0,Range,R   ,Last,Out ) :- 
	Cdf is 1 - (SumLeft0/Range),
	(Cdf =< R
	->  Out=Last 
	;   SumLeft is SumLeft0 + K,
        any1(T,SumLeft,Range,R,K=V,Out)). 	

%%%% test rig
bests(L,N,B) :- about(best,N,_,_,B0),bests1(L,B0,B).

bests1([]) --> !.
bests1([K=V|T]) --> best(K=V,S), {blurt(S)},bests1(T).

pick2(B,One,Two) :- any(B,One),any(B,Two),!.
picks(B,M) :- picks(B,M,'~p').
picks(B,M,Report) :-
	time(bagof(V,  N^B^K^(
                          between(1,M,N), 
                          any(B,K=V)
                         ),L1)),
	msort(L1,L2), 
	forall(member(X,L2),
           format(Report,[X])),
 	nl.
