%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % spec.pl :- op(999,xfx,if). :- op(998,xfy,or). :- op(997,xfy,and). :- op(995,fx, not). :- op(994,xfy, has). :- op(993,xfx, of). :- op(992,xfx, in). :- op(991,xfx, to). myspace('/Users/timm/svns/wisp/var/timm/10/310/src/prolog/4/0/zmyspace.pl'). mine(X) :- nonvar(X), myspace(File), predicate_property(X,file(File)). term_expansion(A if B,(A :- B)). goal_expansion(call(X),X). goal_expansion(Head,Body) :- mine(Head), singleton(Head,Body). clauses(Head,All) :- findall(Head/Body,clause(Head,Body),All). singleton(Head,Body) :- clauses(Head,[Head/Body]). :- myspace(X),load_files([X]). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % zmyspace.pl %------------------------------------------------------- Attribute of Thing = N :- oav(Thing,Attribute,N). Attribute of Thing >= N :- Attribute of Thing = X, X >= N. Attribute of Thing > N :- Attribute of Thing = X, X > N. Attribute of Thing < N :- Attribute of Thing = X, X < N. Attribute of Thing =< N :- Attribute of Thing = X, X =< N. Attribute of Thing in N1 to N2 :- Attribute of Thing = X, X >=N1, X =< N2. Thing has This has That :- Thing has This, Thing has That. Thing has Attribute = N :- Attribute of Thing = N. Thing has Attribute >= N :- Attribute of Thing >= N. Thing has Attribute > N :- Attribute of Thing > N. Thing has Attribute < N :- Attribute of Thing < N. Thing has Attribute =< N :- Attribute of Thing =< N. Thing has Attribute in N1 to N2 :- Attribute of Thing in N1 to N2. /************************************************************** ?- listing(of). B of A=C :- oav(A, B, C). B of A>=D :- oav(A, B, C), C>=D. B of A>D :- oav(A, B, C), C>D. B of A=D, C= 20000 has bloodPressure in 80 to 120 has spouse = Other and Other has bloodPressure in 80 to 120. /************************************************************** ?- listing(happier). happier(A) :- oav(A, income, B), B>20000, oav(A, bloodPressure, C), C>=80, C=<120, oav(A, spouse, D), oav(D, bloodPressure, E), E>=80, E=<120. ***********************************************************/ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % reorder 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). /********************************************* --------------------------------- in :- a, b. out :- a, b. --------------------------------- in :- a, b, b(A, _), c(A, 1). out :- b(A, _), a, b, c(A, 1). --------------------------------- in :- b(A, D), c(B, C, A), d(B, C, 1), f(D). out :- c(B, C, A), b(A, D), d(B, C, 1), f(D). *********************************************/