%-------------------------------------------------------
thing(Thing,Thing) :- wme(_,Thing).
thing(One,Thing)   :- wme(One,Thing).

has(Thing,Stuff,T0,T) :-  
	touch(T0,Thing,Old,New,T), 
	wme(Thing,Old),
	wme(Thing,New), 
	o(Stuff,Old,New). 

o(X has Y) --> o(X), o(Y).
o(Attr =  N    ,T0,T) :- touch(T0,Attr,N ,N,T).
o(Attr :=  N   ,T,T) :- touch(T,Attr,_ ,N,T).
o(state T      ,T,T).
o(Attr >= N1)       --> o(Attr=N),  {N >= N1}.
o(Attr >  N1)       --> o(Attr=N),  {N >  N1}.
o(Attr <  N1)       --> o(Attr=N),  {N <  N1}.
o(Attr =< N1)       --> o(Attr=N),  {N =< N1}.
o(Attr each N)      --> o(Attr=L),  {member(N,L)}.
o(Attr in N1 to N2) --> o(Attr=N0), {N0 >= N1, N0 =< N2}.

o(Attr + N1,  T0,T) :- touch(T0,Attr,N0,N   ,T), N is N0 + N1.
o(Attr - N1,  T0,T) :- touch(T0,Attr,N0,N   ,T), N is N0 - N1.
o(Attr * N1,  T0,T) :- touch(T0,Attr,N0,N   ,T), N is N0 - N1.
o(Attr / N1,  T0,T) :- touch(T0,Attr,N0,N   ,T), N is N0 / N1.
o(Attr ^ N1,  T0,T) :- touch(T0,Attr,N0,N   ,T), N is N0 ^ N1.
o(Attr push N,T0,T) :- touch(T0,Attr,L,[N|L],T).
o(Attr pop  N,T0,T) :- touch(T0,Attr,[N|L],L,T).

type(namep of atomic = _).
type(agep  of integer of 0 to 120 by 1).
type(shoep of integer of 0 to 20 by 1).

type(emp(name of namep,
         age of agep,
         shoesize of shoep)).
type(bag(maxSize of integer = 0 to 10 by 1, 
         items of list).

type(all(emp,love,hate)).

%emp ==> emp : emp
%set of emp ==> emp of list of emp

of(X,T,T) :- type(X,T).

test1 --->
	of all,
	emp has name=tim has age = 20 has shoesize>2 has age+20.

test2 ---> of all,
	emp has name=tim.

/**************************************************************
?- 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.


