%-------------------------------------------------------
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 :-
        oav(A, B, C),
        C<D.
B of A=<D :-
        oav(A, B, C),
        C=<D.
B of A in D to E :-
        oav(A, B, C),
        C>=D,
        C=<E.
***********************************************************/
A and B :- A,B.
A or B :- A;B.

happy if wealthy and healthy or wise.

/**************************************************************
?- listing(happy).
happy :-
        (   wealthy,
            healthy
        ;   wise
        ).
***********************************************************/

happier(You) if
   You has income > 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.

***********************************************************/
:- print(22),nl.

r12 
for start 
if  You has income > 20000 
        has bloodPressure in 80 to 120 
        has spouse = Other
    and 
        Other has bloodPressure in 80 to 120
then
	print(You/Other) and nl.

def(emp(name,age,shoeSize)).

