order(In, Out) :-
	count(In,1,L1),        % (a,b) => [1=a,2=b]
	copy_term(L1,L2),      % (a,b) => [1=a,2=b]
	order1(L1,Order),      % [1=a,2=b] => orderd by bindings
	reorder(Order,L2,Out). % e.g. [2=b,1=a] ==> (b,a)

order1([],[]).
order1([H|T],[Best|Bests]) :-
	setof(One, H^T^order2([H|T],One), [_*Best|_]),
	less1([H|T],Best=Next,Rest), % pull that one from the rest
	numbervars(Next,0,_),        % bind everything in Next
	order1(Rest,Bests).          % explore the Rest

order2(L,Unbound*N) :-
	less1(L,N=One,Rest),
	numbervars(One,0,_),         % bind everything in one
	numbervars(Rest,0,Unbound).  % count the remaining variables 

reorder([_],[_=Last],Last).
reorder([H1,H2|T],L0,(Next,Rest)):-
	less1(L0,H1=Next,L),
	reorder([H2|T],L,Rest).

count((X,Y),N,[N=X|Z]) :- !, N1 is N + 1,count(Y,N1,Z).
count(X,    N,[N=X]).

less1([H|T],H,T).
less1([H|T],Out, [H|Rest]) :-
    less1(T,Out,Rest).

show(What,X) :-
		not(not(portray_clause(What :- X))).

demo1(1,(a,b)).
demo1(2,(a,b,b(X,_), c(X,1))).
demo1(3,(b(W,Z), c(X,Y,W),d(X,Y,1), f(Z))).

demos :-
	forall(demo1(_,In), demos1(In)).

demos1(In) :-
	format('\n---------------------------------\n',[]), 
	show(in,In),order(In,Out), show(out,Out).	
