Go to the previous, next section.
Prolog Objects is an extension to SICStus Prolog for flexible structuring, sharing and reuse of knowledge in large logic programming applications. Prolog Objects enhances Prolog with an expressive and efficient object-oriented programming component.
Prolog Objects is based on the notion of prototypes. In object-oriented programming a prototype is an object that represents a typical behavior of a certain concept. A prototype can be used as is or as a model to construct other objects that share some of the characteristics of the prototypical object. These specialized objects can themselves become prototypes used to construct other objects and so forth. The basic mechanism for sharing is by inheritance and delegation. Inheritance is known for most readers. By using the delegation mechanism an object can forward a message to another object to invoke a method defined by the recipient but interpreted in the context of the sender.
In Prolog Objects, an object is a named collection of predicate definitions. In this sense an object is similar to a Prolog module. The object system can be seen as an extension of SICStus Prolog's module system. In addition an object may have attributes that are modifiable. Predicate definitions belonging to an object are called methods. So, an object is conceptually a named collection of methods and attributes. Some of the methods defined for an object need not be stored explicitly within the object, but are rather shared with other objects by the inheritance mechanism.
The Object system allows objects to be defined in a file, or dynamically created during the execution of a program. Objects defined in a file are integrated into SICStus Prolog in a way similar to definite clause grammars. That is to say, objects have a specific syntax as Prolog terms, and can be loaded and expanded into Prolog code. When an object is created, during load-time, or run-time, it inherits the methods and attributes of its prototypical object(s). Objects defined in a file can be either static or dynamic. Also methods can be either dynamic or static. these properties are inherited by subobjects. Objects created during execution are dynamic.
The inheritance mechanism is implemented using the importation mechanism of
the module system. The default inheritance is an inheritance by
overriding mechanism, which means that if a method is defined locally, and
the same method is defined in a super-object, then the clauses of the
super-method are not part of the definition of the local one. As usual in
Prolog, methods can be nondeterminately defined, and alternative answers can
be retrieved through backtracking. Using the delegation mechanism, other
methods for knowledge sharing can be implemented by the user. In
Objects, there is an initial prototypical proto-object called object
,
from which other objects may be constructed, directly or indirectly.
To load the Prolog Objects library, enter the query:
| ?- use_module(library(objects)).
Prolog Objects defines some new infix and prefix operators, and redefines some of the built-in ones. The following operators become installed:
:- op(1200, xfy, [ & ]). :- op(1198, xfx, [ :- ]). :- op(1198, fx, [ :- ]). :- op(550, xfx, [ ::, <: ]). :- op(550, fx, [ ::, <: ]).
object-identifier :: { sentence-1 & sentence-2 & : sentence-n }.
where object-identifier is a Prolog term that is either an atom or a compound term of the form functor(V1,...,Vn), where V1,...,Vn are distinct variables. The object body consists of a number of sentences, possibly none, surrounded by braces, where each sentence is either a method-directive, to be executed when the object is created, or a method-clause. A method is a number of method-clauses with the same principal functor. A method-clause has a clausal syntax similar to that of Prolog, but instead of usual predicate calls in the body of a clause there are method-calls. Ordinary Prolog goals are also allowed in a prefixed form, using ':' as a prefix. A method-directive is a directive which contains method-calls.
All sentences are subject to term expansion (see section Term and Goal Expansion, built-in
expand_term/2
) before further processing, so in particular
definite clause grammar syntax can be used in method-clauses.
Method-clauses are declared similarly to Prolog clauses. Thus a method-clause can be either a unit-clause or a non-unit-clause. We also allow a default catch-all method-clause as the last clause in an object body. The catch-all clause has as its head a Prolog variable, in order to match messages that are not previously defined or inherited in the object. It can be used to implement alternative inheritance mechanisms.
Goals in the body of a non-unit clause have the normal control structures of Prolog:
Atomic goals in the body of a method-clause may be one of the following:
Message sending and delegation will be explained later (see section Self, Message Sending, and Message Delegation).
The following is a definition for the object list_object
. It is
constructed from three methods: append/3
, member/2
, and
length/2
. Note that the calls to append/3
and
length/2
are to the local definition, whereas the member/2
call is to the predicate imported from the Prolog library module lists
.
list_object :: { :- :use_module(library(lists), [append/3,member/2]) & append([], L, L) & append([X|L1], L2, [X|L3]) :- :: append(L1, L2, L3) & member(X, L) :- :member(X,L) & length([], 0) & length([_|L], N) :- :: length(L, N1), :(N is N1+1) }.
The following object apt_1
could be part of a larger database
about free apartments in a real-estate agency:
apt_1 :: { super(apartment) & street_name('York') & street_number(100) & wall_color(white) & floor_surface(wood) }.
Another way to define apt_1
is by using attributes. These can be
retreived and modified efficiently by the methods get/1
and
set/1
respectively.
apt_1 :: { super(apartment) & attributes([ street_name('York'), street_number(100), wall_color(white), floor_surface(wood)]) }.
Defining objects for easy reuse is a very important property for reducing the cost of large projects. One important technique is to define prototypes in a parameterized way, so that various instantiations of a prototype correspond to different uses. Parameterized or generic objects have been used for this purpose in other object-oriented systems. An object-identifier can be a compound term. The arguments of the term are parameters that are visible in the object-body. Here we show one example. Other examples and techniques that use this facility has been investigated extensively in [McCabe 92].
The following is an object sort
that sorts lists of different
types. sort
has a parameter that defines the type of the
elements of the list. Notice that Type is visible to all methods
in the body of sort
, and is used in the method
partition/4
. In the query, we use sort(rat)
to sort a
list of terms denoting rational numbers. We must therefore define a
rat
object and its <
method also:
rat :: { (P/Q < R/S) :- :(P*S < Q*R) }. sort(Type) :: { :- :use_module(library(lists), [append/3]) & qsort([], []) & qsort([P|L], S) :- partition(L, P, Small, Large), qsort(Small, S0), qsort(Large, S1), :append(S0, [P|S1], S) & partition([], _P, [], []) & partition([X|L1], P, Small, Large) :- ( Type :: (X < P) -> Small = [X|Small1], Large = Large1 ; Small = Small1, Large = [X|Large1] ), partition(L1, P, Small1, Large1) }. | ?- sort(rat) :: qsort([23/3, 34/11, 45/17], L). L = [45/17,34/11,23/3]
Parameterized objects are interesting in their own right in Prolog even if one is not interested in the object-oriented paradigm. They provide global context variables in a Prolog program without having to add such variables as additional context arguments to each clause that potentially uses the context.
In Prolog Objects, each method is executed in the context of an object.
This object may not be the static object where the method is declared.
The current contextual object is used to determine dynamically which
attributes are accessed, and which methods are called. This leads to a
mechanism known as dynamic binding. This object can be retrieved using
the universal method self(S)
, where S will be bound
to the current contextual object.
When a message is sent to an object, the corresponding method will be executed in the context of the target object. A message delegated to an object will invoke a method that is executed in the context of the message-delegation operation.
The following objects physical_object
, a
, and b
are
written using the default notations for sending and delegation, hiding the
contextual variable Self:
physical_object :: { volume(50) & density(100) & weight(X) :- volume(V), density(D), :(X is V*D) }. a :: { volume(5) & density(10) & Method :- physical_object <: Method }. b :: { volume(5) & density(10) & Method :- physical_object :: Method }.
Notice that the difference between the objects a
and b
is
that a
delegates any message except volume(_)
and
density(_)
to physical_object
while b
sends
the message to physical_object
. We may now ask
| ?- a :: weight(X), b :: weight(Y). X = 50 Y = 5000
To get hold of the current contextual object, the universal method
self(S)
is provided. Another way to send a message to
Self is to use the constant self
. So the following two
alternative definition of physical_object
are equivalent to the
previous one:
physical_object :: { volume(50) & density(100) & weight(X) :- self(S), S::volume(V), S::density(D), :(X is V*D) }. physical_object :: { volume(50) & density(100) & weight(X) :- self::volume(V), self::density(D), :(X is V*D) }.
The Prolog Objects system implements a default inheritance mechanism. By
declaring within an object which objects are super-objects, the hierarchy of
objects are maintained. The system also maintains for each object its
immediate sub-objects (i.e. immediate children). Each object may also call
Prolog predicates. At the top of the hierarchy, the proto-object
object
provides various services for other objects. If object
is
not used at the top of the hierarchy many services will not be available for
other objects (check what methods are available in object
by sending
the message method/1
to object
).
Immediate super-objects are declared by defining the method
super/2
within the object. (Any definition
super(Super)
is transformed to
super(Super,[])
). The objects declared by super/2
are the immediate objects from which a method is inherited if not
defined within the object. This implies that the inheritance mechanism
is an overriding one. One could possibly have a union inheritance,
whereby all clauses defining a method are collected from the super
hierarchy and executed in a Prolog fashion. This can easily be
programmed in Prolog Objects, using delegation to super objects.
The following example shows some objects used for animal classification.
animal :: {}. bird :: { super(animal) & skin(feather) & habitat(tree) & motions(fly) }. penguin :: { super(bird) & habitat(land) & motions(walk) & motions(swim) & size(medium) }. | ?- penguin :: motions(M). M = walk ; M = swim ; no | ?- penguin :: skin(S). S = feather ; no
The following is an example of multiple inheritance: an object john
is
both a sportsman and a professor:
john :: { super(sportsman) & super(professor) & : }.
Inheritance will give priority to the super-objects by the order defined in
the super/2
method. Therefore in the above example John's
characteristics of being a sportsman will dominate those of being professor.
Other kinds of hierarchy traversal can be programmed explicitly using the
delegation mechanism.
It is possible to be selective about what is inherited by
using the method super/2
. Its first argument is the
super object, and its second is a list of the methods that
will not be inherited from the super object.
In Prolog Objects, the visible predicates of the source module
(context) for the object definition may be called in the body of a
method. (The :
prefix is used to distinguish such calls from
method calls.) Any (:
prefixed) directives occurring among
the method-clauses are also executed in the same source module. For
example, to import into the source module and call the public
predicates of a module, the built-in predicate use_module/2
and
its variants may be used:
some_object :: { :- :use_module(library(lists), [append/3]) & double_list(X, XX) :- :append(X,X,XX) }.
Two methods provided by the initial object object
are
super/1
and sub/1
.
(Note that any definition of super/1
, except the one in
object
, is transformed to super/2
).
super/1
if sent to an object will return the immediate parents of
the object. sub/1
will return the immediate children of the
object if any. It is important to note that this service is provided
only for objects that have object
as their initial ancestor.
| ?- john :: super(S), S :: sub(john). S = sportsman ; S = professor ; no
The sub/1
property allows programs to traverse object hierarchies from a
root object object
down to the leaves.
super
is
provided. The calls:
super :: method, or super <: method
mean: send or delegate (respectively) method to the super-objects
according to the inheritance protocol. A simple example illustrates this
concept: assume that john
in the above example has three id-cards, one
stored in his sportsman prototype identifying the club he is member of, one
stored in his professor prototype identifying the university he works in, and
finally one stored locally identifying his social-security number. Given the
following methods in the object john
:
m1(X) :- super <: id_card(X) & m2(X) :- super(S), S <: id_card(X) &
one may ask the following:
| ?- john :: m1(X). % will follow the default inheritance and returns: X = johns_club ; | ?- john :: m2(X). % will backtrack through the possible supers returning: X = johns_club ; X = johns_university ;
m/n
is linked
to object some_object
, we just add a method for this:
m(X1, ..., Xn) :- some_object <: m(X1, ..., Xn) &
When an object is declared and compiled into Prolog Objects, its methods
cannot be changed during execution. Such an object is said to be
static. To be able to update any method in an object, the object has to
be declared dynamic. There is one exception, the inheritance hierarchy
declared by super/(1-2)
cannot be changed. By including the fact
dynamic
as part of the object body, the object becomes dynamic:
dynamic_object :: { dynamic & : }.
some_object :: { dynamic F/N & : }.
Each book in a library can be represented as an object, in which the
name of the book is stored, the authors, and a borrowing history
indicating when a book is borrowed and when it is returned. A history
item may have the form
history_item(Person,Status,Date)
where
Status is either borrowed
or returned
, and
Date has the form YY-MM-DD, for YY year, MM month, DD day.
A typical book book_12
could have the following status. Note that
history_item/3
is dynamic:
book_12 :: { super(book) & title('The Art of Prolog') & authors(['Leon Sterling', 'Ehud Shapiro']) & dynamic history_item/3 & history_item('Dan Sahlin', returned, 92-01-10) & history_item('Dan Sahlin', borrowed, 91-06-10) & : }.
Dynamic methods that are stored in an object can be updated, as in usual
Prolog programs, by sending assert
and retract
messages
directly to the object.
For example, to borrow a book the following method could be defined in the
object book
. We assume that the top most history_item
fact is
the latest transaction, and there is an object date
from which we can
get the current date.
borrow(Person) :- history_item(_Person0, Status, _Date0), !, ( Status = returned -> date::current(Date), asserta(history_item(Person, borrowed, Date)) ; :display('book not available'), :ttynl ) &
When an object is created, it will inherit from its parents their dynamic behavior. Methods that are declared dynamic in a parent, will be copied into the object, and its dynamic behavior preserved.
a:: { super(object) & dynamic p/1 & p(1) & p(2) } b :: { super(a) } | ?- b::p(X). X = 1 ? ; X = 2 ? ; no | ?- b::asserta(p(3)). yes | ?- b::p(X). X = 3 ? ; X = 1 ? ; X = 2 ? ; no
Notice that by redeclaring a method to be dynamic in a subobject, amounts to redefining the method, and overriding of the parent definition will take effect.
c :: { super(a) & dynamic p/1 } | ?- c::p(X). no
As with dynamically declared objects, the full flexibility of Prolog
Objects is achieved when objects are created at runtime. Anything,
except the inheritance hierarchy, can be changed: methods can be added
or deleted. The services for object creation, destruction, and method
modification are defined in the proto-object object
.
The object vehicle
is created having the proto-object object
as
super, followed by creating moving_van
with vehicle
as super,
followed by creating truck
.
| ?- object :: new(vehicle), vehicle :: new(moving_van), moving_van :: new(truck). yes | ?- truck :: super(X), vehicle :: sub(X). X = moving_van ; no
Add some facts to vehicle
and truck
with initial value equal to
[]
.
| ?- vehicle :: assert(fuel_level([])), vehicle :: assert(oil_level([])), vehicle :: assert(location([])), truck :: assert(capacity([])), truck :: assert(total_weight([])). yes
When new objects are created, it is possible to pass parameters. The following example shows:
In the previous examples one could pass parameters to an object as follows,
using the method augment/1
.
| ?- vehicle :: augment({ new_attrs(Instance, Attribute_list) :- self :: new(Instance), :: assign_list(Attribute_list, Instance) & assign_list([], Instance) & assign_list([Att|List], Instance) :- :: assign(Att, Instance), :: assign_list(List, Instance) & assign(P, Instance) :- Instance :: assert(P) }). yes % create a new 'truck' | ?- vehicle :: new_attrs(truck, [capacity([]),total_weight([])]). yes
super
. Notice that without a delegation
mechanism this would not be possible, since the Self would have
changed.
So assume that we want to print on
the screen "p is augmented" whenever the fact p(X)
is asserted
in an object foo
, we just redefine assert/1
:
foo :: { super(object) & dynamic p/1 & p(0) & p(1) & assert(p(X)) :- !, /* assert/1 is redefined for p(X) */ super <: assert(p(X)), :display('p is augmented'), :ttynl & assert(M) :- /* delegating assert(_) messages */ super <: assert(M) & : }.
Objects are relatively heavy weight. To be able to create efficiently
light weight objects, we introduce the notion of instances. An
instance is an object with restricted capability. It is created from
an object that is considered its class. It gets a copy of the
attributes of its class. These can be modified by get/1
and
set/1
. An instance cannot be a class for other
instances. Instances are in general very efficient, both in space and
access/modification time. The attribute '$class'/1
will store
the identity of the class of the instance including parameters.
super(Object)
is
translated to super(Object,[])
.
object
covering the cases of unexpanded
calls.
object
provides basic methods that are available
to all other objects by delegation:
super(Object)
are translated to the
universal method super/2
.
Name/Arity
.
asserta
places Fact before any old facts. The other forms
place it after any old facts. A pointer to the asserted fact is
returned in the optional argument Ref, and can be used by the
Prolog built-in predicates erase/1
and instance/2
.
augmenta
places the new clauses
before any old clauses. The other forms place it after any old clauses.
utility
provides methods that could be used in user
programs. utility
has object
as its super-object.
As already mentioned, object definitions are expanded to Prolog clauses much as definite clause grammars. This expansion is usually transparent to the user. While debugging a Prolog Objects program, however, the expanded representation may become exposed. This section will explain in detail the source expansion, so as to give the user the possibility to relate back to the source code during a debugging session. The inheritance mechanism, based on module importation, is also described.
First of all, every statically defined object will translate to several Prolog clauses belonging to a unique object module with the same identity as the object-identifier. Object modules are significantly cheaper to create than ordinary modules, as they do not import the built-in Prolog predicates.
The module will contain predicates implementing an object declaration, the method code, imported methods and parameter transfer predicates. These predicates will be described in detail below, using the notational convention that variable names in italics are syntactic variables that will be replaced by something else in the translation process.
The inheritance mechanism is based on the importation mechanism of the
Prolog module system. When an object is created, whether loaded from
file or at runtime by new/(1-2)
, the method predicates
(i.e. predicates implementing the methods) visible in the immediate
supers are collected. After subtracting from this set the method
predicates which are locally defined, and those that are specified in
the don't-inherit-list , the resulting set is made visible in the
module of the inheriting object by means of importation. This implies
that inherited methods are shared, expect dynamic methods.
Dynamic methods are inherited in a similar way with the big difference that they are not imported but copied. Even dynamic declarations (methods without clauses) are inherited.
Inheritance from dynamic objects differs in one aspect: Static predicates visible in a dynamic object are not imported directly from the dynamic object but from the static object from where it was imported to the dynamic object. This makes an inheriting object independent of any dynamic ancestor object after its creation.
Attributes are based on an efficient term storage associated to
modules. The attributes for an object is collected from its ancestors
and itself at compile time and used for initialization at load
time. The methods for accessing attributes, get/1
and
set/1
, are inlined to primitive calls whenever possible. They
should hence not be redefined.
Instances are different from other objects in that they do not
inherit. Instead they share the predicate name space with its class
object. They do however have their own attributes. At creation, an
instance gets a copy of its class objects attributes. The reserved
attribute '$class'/1
, which is present in any object, is used for
an instance to hold its class object identifier. The purpose of this
is mainly to store the parameters of the class object when the
instance is created.
The object declaration is only used by certain meta-programming operations. It consists of a fact
'$so_type'(Object, Type).
where Object is the object-identifier, and Type is
either static
or dynamic
. If the type is static
,
the other generated predicates will be static, otherwise they will be
dynamic.
Each method clause translates to a Prolog clause with two extra arguments: Self (a variable) and Myself. The latter argument is needed to cater for passing object parameters to the method body which is desribed further in next section.
The method body is translated to a Prolog-clause body as follows.
The code is traversed, and the goals are transformed according to the
following transformation patterns and rules. In the transformation
rules, the notation Msg(X,Y)
denotes the term
produced by augmenting Msg by the two arguments X and
Y:
objects:call_from_body(Goal,Self,Myself,Src)
where Src is the source module. objects:call_from_body/4
will meta-interpret Goal
at runtime.
Myself:Msg(Myself,Myself)
if Msg is a non variable. Otherwise, it is translated to
objects:call_object(Myself, Msg, Myself)
.
Myself:Msg(Self,Myself)
if
Msg is a non variable. Otherwise, it is translated to
objects:call_object(Myself, Msg, Self)
.
objects:call_super_exp(Myself,Msg(Super,Myself),Super)
if Msg is a non variable. call_super_exp/3
searches the
supers of Myself. Super is bound to the super object where
the method is found. If Msg is a variable, the goal is
translated to
objects:call_super(Myself,Msg,Super,Super)
which expands Msg and performs otherwise the same actions as
call_super_exp/3
.
objects:call_super_exp(Myself,Msg(Self,Myself),Super)
if Msg is a non variable. call_super_exp/3
searches the
supers of Myself. Super is bound to the super object where
the method is found. If Msg is a variable, the goal is
translated to
objects:call_super(Myself,Msg,Self,Super)
which expands Msg and performs otherwise the same actions as
call_super_exp/3
.
Obj:Msg(Obj,Obj)
.
objects:call_object(Obj,Msg,Obj)
.
Obj:Msg(Self,Obj)
.
functor(Obj,O,_),
O:Msg(Self,Obj)
.
objects:call_object(Obj,Msg,Self)
.
Self :: Msg
.
Module:Goal
.
Src:Goal
where Src is the
source module.
To illustrate the expansion, consider the object history_point
directives, all executed in the history_point
module:
:-objects:create_object(history_point, [point-[]], [attributes/3,display/3,move/4,new/4,print_history/3,super/4], [], [y(0),x(0),history([])], tree(history_point,[tree(point,[tree(object,[])])])). history_point:super(point, [], _, history_point). history_point:attributes([history([])], _, _). history_point:display(A, B, _) :- objects:call_super_exp(history_point, display(A,B,C), C), history_point:print_history(A, B, history_point). history_point:'$so_type'(history_point, static). history_point:move(A, B, C, _) :- objects:call_super_exp(history_point, move(A,B,C,E), E), prolog:'$get_module_data'(C, history, D), prolog:'$set_module_data'(C, history, [(A,B)|D]). history_point:print_history(A, B, _) :- prolog:'$get_module_data'(B, history, C), A:format('with location history ~w~n', [C], A, A). history_point:new(A, xy(D,E), B, _) :- objects:call_super_exp(history_point, new(A,xy(D,E),B,C), C), prolog:'$set_module_data'(A, history, [(D,E)]).
The directive create_object/6
creates the object, performs the
inheritance by importation, and initializes attributes. The last
argument is a tree representing the ancestor hierarchy during
compilation. It is used to check that the load time and compile time
environments are consistent.
As can be seen in the expanded methods above, the second additional argument is simply ignored if the object has no parameter. In contrast regard the following objects:
ellipse(RX,RY,Color) :: { color(Color) & area(A) :- :(A is RX*RY*3.14159265) }. circle(R,Color) :: { super(ellipse(R,R,Color)) }. red_circle(R) :: { super(circle(R,red)) }.
... and their expansions:
ellipse(_, _, _):'$so_type'(ellipse(_,_,_), static). ellipse(_, _, _):area(A, _, B) :- B:'$fix_param'(ellipse(C,D,_), B), user:(A is C*D*3.14159265). ellipse(_, _, _):color(A, _, B) :- B:'$fix_param'(ellipse(_,_,A), B). ellipse(_, _, _):'$fix_param'(ellipse(B,C,D), A) :- objects:object_class(ellipse(B,C,D), A). circle(_, _):'$so_type'(circle(_,_), static). circle(_, _):super(ellipse(A,A,B), [], _, circle(A,B)). circle(_, _):'$fix_param'(circle(B,C), A) :- objects:object_class(circle(B,C), A). circle(_, _):'$fix_param'(ellipse(B,B,C), A) :- objects:object_class(circle(B,C), A). red_circle(_):'$so_type'(red_circle(_), static). red_circle(_):super(circle(A,red), [], _, red_circle(A)). red_circle(_):'$fix_param'(red_circle(B), A) :- objects:object_class(red_circle(B), A). red_circle(_):'$fix_param'(circle(B,red), A) :- objects:object_class(red_circle(B), A). red_circle(_):'$fix_param'(ellipse(B,B,red), A) :- objects:object_class(red_circle(B), A).
The second additional argument contains the receiver of a method
call. If the method makes use of any parameter of the object where it is
defined, it places a call to the reserved predicate $fix_param/2
in the module of the receiver. The purpose of this call is to bind the
parameters used in the method to appropriate values given by the
receiver. The receiver may be the object where the method is defined or
any of its subs. In order to service these calls, a clause of
$fix_param/2
is generated for each ancestor having
parameters. Such a clause may be regarded as the collapsed chain of
super/(1-2)
definitions leading up to the ancestor.
The call objects:object_class(Class,Object)
serves to
pick up the '$class'/1
attribute if Object is an instance,
otherwise Class is unified with Object.
The following trace illustrates how parameters are transfered:
| ?- red_circle(2.5)::area(A). 1 1 Call: red_circle(2.5)::area(_A) ? 2 2 Call: ellipse(_,_,_):area(_A,red_circle(2.5),red_circle(2.5)) ? 3 3 Call: red_circle(_):$fix_param(ellipse(_B,_,_),red_circle(2.5)) ? 4 4 Call: objects:object_class(red_circle(_B),red_circle(2.5)) ? 4 4 Exit: objects:object_class(red_circle(2.5),red_circle(2.5)) ? 3 3 Exit: red_circle(_):$fix_param(ellipse(2.5,2.5,red),red_circle(2.5)) ? 5 3 Call: _A is 2.5*2.5*3.14159265 ? 5 3 Exit: 19.6349540625 is 2.5*2.5*3.14159265 ? 2 2 Exit: ellipse(_,_,_):area(19.6349540625,red_circle(2.5),red_circle(2.5)) ? 1 1 Exit: red_circle(2.5)::area(19.6349540625) ? A = 19.6349540625 ?
animal :: { super(object) & relative_size(S) :- size(Obj_size), super(Obj_prototype), Obj_prototype :: size(Prototype_size), :(S is Obj_size/Prototype_size * 100) }. bird :: { super(animal) & moving_method(fly) & active_at(daylight) }. albatross :: { super(bird) & color(black_and_white) & size(115) }. kiwi :: { super(bird) & moving_method(walk) & active_at(night) & size(40) & color(brown) }. albert :: { super(albatross) & size(120) }. ross :: { super(albatross) & size(40) }. | ?- ross :: relative_size(R). R = 34.78
The concept of instance variables is readily available as the variables
belonging to the instances created dynamically and not to the class of
the instances. For example, each instance of the class point
will have two instance variables, x
and y
, represented by
the attributes x/1
and y/1
. The traditional class
variables are easily available by accessing the same attributes in the
associated class.
Another issue is the pattern used to create new instances. For example,
to create an instance of the class history_point
, the following
code is used:
new(Instance, xy(IX,IY)) :- super <: new(Instance, xy(IX,IY)), Instance :: set(history([(IX,IY)])) &
Note that the delegation of new/2
to super
is necessary in
order to create an object whose super is history_point
and not
point
.
The example shows how delegation can be effective as a tool for flexible
sharing of concepts in multiple inheritance. Four prototypes
are defined: point
, history_point
, bounded_point
,
and bh_point
. The latter is a bounded history point.
An instance of the point
class is a point that moves in 2-D space
and that can be displayed. An instance of the history_point
class is similar to an instance of the point
class but also keeps
a history of all the moves made so far. An instance of
bounded_point
is similar to an instance of point
but moves
only in a region of the 2-D space. Finally an instance of
bh_point
inherits most of the features of a bounded_point
and a history_point
.
The default inheritance does not work for the methods display/1
and move/2
in bh_point
. Inheritance by delegating
messages to both supers of bh_point
results in redundant actions,
(moving and displaying the point twice). Selective delegation solves
the problem. Taken from [Elshiewy 90].
point :: { super(object) & attributes([x(0),y(0)]) & xy(X, Y) :- get(x(X)), get(y(Y)) & new(Instance, xy(IX,IY)) :- super <: instance(Instance), Instance :: set(x(IX)), Instance :: set(y(IY)) & location((X,Y)) :- <: xy(X,Y) & move_horizontal(X) :- set(x(X)) & move_vertical(Y) :- set(y(Y)) & move(X, Y) :- <: move_horizontal(X), <: move_vertical(Y) & display(Terminal) :- <: xy(X, Y), Terminal :: format('point at (~d,~d)~n',[X,Y]) }. history_point :: { super(point) & attributes([history([])]) & new(Instance, xy(IX,IY)) :- super <: new(Instance, xy(IX,IY)), Instance :: set(history([(IX,IY)])) & move(X, Y) :- super <: move(X, Y), get(history(History)), set(history([(X,Y)|History])) & display(Terminal) :- super <: display(Terminal), <: print_history(Terminal) & print_history(Terminal) :- get(history(History)), Terminal :: format('with location history ~w~n', [History]) }. bounded_point :: { super(point) & attributes([bounds(0,0,0,0)]) & new(Instance, Coords, Bounds) :- super <: new(Instance, Coords), Instance :: set_bounds(Bounds) & set_bounds(Bounds) :- set(Bounds) & move(X, Y) :- <: bound_constraint(X, Y), !, super <: move(X, Y) & move(_, _) & bound_constraint(X, Y) :- get(bounds(X0, X1, Y0, Y1)), :(X >= X0), :(X =< X1), :(Y >= Y0), :(Y =< Y1) & display(Terminal) :- super <: display(Terminal), <: print_bounds(Terminal) & print_bounds(Terminal) :- get(bounds(X0, X1, Y0, Y1)), Terminal :: format('xbounds=(~d,~d), \c ybounds=(~d,~d)~n', [X0,X1,Y0,Y1]) }. bh_point :: { super(history_point) & super(bounded_point) & new(Instance, Coords, Bounds) :- history_point <: new(Instance, Coords), Instance :: set_bounds(Bounds) & move(X, Y) :- bounded_point <: bound_constraint(X, Y), !, history_point <: move(X, Y) & move(_, _) & display(Terminal) :- bounded_point <: display(Terminal), history_point <: print_history(Terminal) }. tty :: { format(X, Y) :- :format(X, Y) }. point at (8,12) xbounds=(5,15), ybounds=(5,15) with location history [(8,12),(9,11)]
- faults - electrical | - lights | - starting | - starter_motor | - sparking | - plugs | - distributer - fuel_system - mechanical
The general diagnosis method is defined in the object faults
,
whereas the cause-effect relationships are defined in the specific
objects e.g. the object distributor
.
This program heavily uses the sub/1
method. We have tried to be
as close as possible to the original formulation.
faults :: { super(utility) & dynamic(told/2) & /* no fault is the default */ fault(_, _) :- :fail & findall :- <: restart, :: sub(Sub), Sub :: find(Where, Fault), <: print(Where, Fault), :fail & findall & print(Where, Fault) :- :writeseqnl('Location : ', [Where]), :writeseqnl('Possible Fault : ', [Fault]), :nl & find(Where, Fault) :- self(Where), fault(FaultNum, Fault), \+ (effect(FaultNum, S), contrary(S, S1), exhibited(S1) ), \+ (effect(FaultNum, SymptomNum), \+ exhibited(SymptomNum)) & find(Where, Fault) :- sub(Sub), Sub :: find(Where, Fault) & exhibited(S) :- :: told(S, R), !, R = yes & exhibited(S) :- symptom(S,Text), ( :yesno([Text]) -> R = yes ; R = no ), :: asserta(told(S,R)), R = yes & restart :- :: retractall(told(_,_)) }. electrical :: { super(faults) }. fuel_system :: { super(faults) }. mechanical :: { super(faults) }. lights :: { super(electrical) }. sparking :: { super(electrical) }. starting :: { super(electrical) }. starter_motor :: { super(electrical) }. plugs :: { super(sparking) }. engine :: { super(mechanical) }. cylinders :: { super(engine) }. distributor :: { super(sparking) & /* faults */ fault('F1001', 'Condensation in distributor cap') & fault('F1002', 'Faulty distributor arm') & fault('F1003', 'Worn distributor brushes') & /* symptoms */ symptom('S1001', 'Starter turns, but engine does not fire') & symptom('S1002', 'Engine has difficulty starting') & symptom('S1003', 'Engine cuts out shortly after starting') & symptom('S1004', 'Engine cuts out at speed') & /* symptoms contrary to each other */ contrary('S1002', 'S1001') & contrary('S1003', 'S1001') & /* causal-effect relationship */ effect('F1001', 'S1001') & effect('F1002', 'S1001') & effect('F1002', 'S1004') & effect('F1003', 'S1002') & effect('F1003', 'S1003') }. yesno(Value) :- write(Value), nl, read(yes). writeseqnl(Prompt, L) :- write(Prompt), write_seq(L). write_seq([]). write_seq([X|L]) :- write(X), write(' '), write_seq(L), nl. faults :- faults :: findall. | ?- faults. [Starter turns, but engine does not fire] |: yes. Location : distributor Possible Fault : Condensation in distributor cap [Engine cuts out at speed] |: yes. Location : distributor Possible Fault : Faulty distributor arm yes | ?- faults. [Starter turns, but engine does not fire] |: no. [Engine has difficulty starting] |: yes. [Engine cuts out shortly after starting] |: yes. Location : distributor Possible Fault : Worn distributor brushes
Go to the previous, next section.