% factor=2
%     sorted: 4948/2  <=== unaffected by P(BEST)
%     random: 4801/149

% factor = 1
%     sorted :   595/4355
%     random :  1204/3746

% no support,
%    random sort : yes/no : 2903/2047
%    sorted      : yes/no : 3199/1751
% support 
%    random sort : yes/no : 4891/59
%    sorted      : yes/no : 4915/35 <<== uneffected 

r(Top,_,Z) :- r(Top,Z).

r(Top,Z) :- X is 1000000000, Z is random(X)/X * Top.

eq0(Es,Fp,All,Out) :-  f(Es,Fp,F), Out is F * Fp/All.

eq(A,B,X) :- X is A^2/(A+B).

f([H|T],N,S) :- f(T,N,H/N,S).
f([],_,S,S).
f([H|T],N,S0,S) :- S1 is S0*H/N,f(T,N,S1,S).

some(Top,L) :- length(L,100), maplist(r(Top ),L,L).

go(PBest0,Yes/No) :-
	PBest=PBest0,
    All=10000,
	Bests is PBest/100 * All,
	Rests is All - Bests,
	some(Bests,Best),
	some(Rests,Rest),
    score(Best,Rest,Scores0,Bests,Rests,All),
	sort(Scores0,Scores1),
	reverse(Scores1,Scores),
	flag(no,_,0),
	flag(yes,_,0),
	forall(tests(Scores,Bests,Rests,All),true),
	flag(no,No,No),
	flag(yes,Yes,Yes).

tests(Scores,Bests,Rests,All) :-
	 between(1,100,I),
	 Gap is 100 - I,
	 between(1,Gap,Delta),
	 I1 is I + Delta,
	 %I1 > I,
	 tests(Scores,I, Bests,Rests,All,ScoresI),
	 tests(Scores,I1,Bests,Rests,All,ScoresI1),
	 (ScoresI > ScoresI1 -> 
              flag(yes,Yes,Yes+1); 
	      flag(no,No,No+1)).

score([],[],[],_,_,_).
score([Best1|Best],[Rest1|Rest],[Score=Best1/Rest1|Scores],Bests,Rests,All) :-
	eq0([Best1],Bests,All,A),
	eq0([Rest1],Rests,All,B),
	eq(A,B,Score),
	%Score is random(100000),
	score(Best,Rest,Scores,Bests,Rests,All).

tests(Scores,I,Bests,Rests,All,X) :-
	length(Scores1,I),
	append(Scores1,_,Scores),
	extractB(Scores1,Bs),
	extractR(Scores1,Rs),
	eq0(Bs,Bests,All,A),
	eq0(Rs,Rests,All,B),
	eq(A,B,X).

sum([H|T],S) :- sum(T,H,S).
sum([],S,S).
sum([H|T],S0,S) :- S1 is S0+H,sum(T,S1,S).


extractB([],[]).
extractB([_=B/_|T0],[B|T]) :- extractB(T0,T).

extractR([],[]).
extractR([_=_/R|T0],[R|T]) :- extractR(T0,T).

/*
		
new(Y) :-
		member(P,[1,1.05,1.1,1.15,1.2,1.3,2]),
	    news(P,Top,Y).

news(P,Top,Z) :-
		flag(n,_,0),
			flag(yes,_,0),
	N=10000,
	new1(N,P,Top),
		flag(yes,Y,Y),
		flag(n,N,N),
		Z is Y/N.

new1(N,P,Top) :-
		between(1,N,I),
			print(I),
		new2(P,Top).

new2(P,Top) :-
	    repeat,
		r(Top,A),
        r(Top,B),
		B < A,
        r(Top,X1),
        r(Top,X2),
		10^(-10) < X1,
		10^(-10) < X2,
        r(Top,Y1),
        r(Top,Y2),
	    X1 =< Y1,
	    X2 =< Y2,		
		X1 > X2,
		Y1 =< 0.25,
		Y2 =< 0.25,
		flag(n,N,N+1),
		eq1(P,A,B,X1,X1,Y1,Y2,Z1),
		eq2(P,A,B,X1,Y1,Z2),
		(Z1 <Z2 -> flag(yes,Yes,Yes+1); true).
/*
*
prim(P,Top,MaxXValue,[Comp,Score,A,B,X,Y]) :-
        repeat,
	   r(Top,A),
        r(Top,B),
        r(Top,X),
        r(Top,Y),
        A > B, 
        A =< X, 
        B =< Y, 
	X =< MaxXValue,
        eq1(P,A,B,X,Y,Z1),
        eq2(P,A,B,Z2),
        (Z1 >= Z2 
        -> Comp= great, Score=1
        ;  Comp= terrible, Score=0),
	!.


go1s(P,Top,Y) :-
	N=1000,
	bagof(S,P^Top^N^go1(N,P,Top,S),L),
        sum(L,X),
	Y is X*100/N.

go1(N, P,Top,Score) :- 
	between(1,N,_),
	prim(P,Top,1,[_,Score|_]).

go :-
	member(P,[1,1.05,1.1,1.15,1.2,1.3,2]),
	member(Top,[1,0.1,0.01,0.001,0.0001]),
	go1s(P,Top,Y),
	format('~p ~p ~p\n',[P,Top,Y]),
	fail.

trap :-
	tell('sumsout.csv'),
	forall(trap1,true),
	told.

trap1 :-
	format('~p,~p,~p,~p,~p\n',[a,b,x,y,comp]),
	between(1,1000,_),
	prim(1,1,1,[Comp,_Score,A,B,X,Y]),
	format('~p,~p,~p,~p,~p\n',[A,B,X,Y,Comp]).
*/

*/
