object(supermarket).          %  objects in figure 1.6
object(check_out_till_line).
object(check_out_station).
class(shop).                  %  classes and objects used
object(shelving_aisles).      %  implicitly
object(freezer_banks).
object(trolley_parks).
object(supermarket).
  % --  define frame for SUPERMARKET --
slot(supermarket,instance_of,shop).
slot(supermarket,location,out_of_town).
slot(supermarket,comprises,[check_out_till_line,shelving_aisles,freezer_banks]).
  % --  define frame for CHECK-OUT TILL LINE --
slot(check_out_till_line,location,supermarket_exit).
slot(check_out_till_line,number,50).
slot(check_out_till_line,comprises,[check_out_station,trolley_parks]).
 
  
    %  RUNNING THIS CODE
%
%  Actually very little you can do with the above except examine
%  specific facts.
%  However, this can be combined with the sort of code you saw
%  in the semantic network to give inheritance etc.
%
%  For example, we might have a default location for a shop
slot(shop,location,town_centre).
%  and other kinds of shop:
object(veras_veggies).
slot(veras_veggies,instance_of,shop).
slot(veras_veggies,sells,vegetables).
%  Inheritance rules can then be written using the 'instance_of' slot:
has_slot(OC,P,V)  :-  slot(OC,P,V).
has_slot(O,P,V)   :-  \+ slot(O,P,V),
                      slot(O,instance_of,C),
                      has_slot(C,P,V).
has_slot(C1,P,V)  :-  \+ slot(C1,P,V),
                      slot(C1,is_a,C2),     %  assume that classes may have 
                      has_slot(C2,P,V).     %  an 'is-a' slot
%  Now you can ask questions about shop locations:
%
%>      has_slot(veras_veggies,location,X).
%
%>      has_slot(supermarket,location,X).
%
%  The former will give the answer 'town_centre' using the inherited 
%  default location from 'shop.  However, the latter should give the
%  answer 'out_of_town' as the supermarket's own slot overrides the
%  shop slot.
%  
 
  
	%  EXAMPLES
%
%>  has_slot(veras_veggies,location,X).    %  default shop location 'town_centre'
%
%>  has_slot(supermarket,location,X).      %  supermarket overrides  location as 'out_of_town'