Combining many-sorted logic and object-oriented programming

Combining many-sorted logic and object-oriented programming

Combining many-sortedlogic and object-oriented programming B M Kim*, K Y Ryu, S R Maeng and J W Cho The logic' language based on many-sorted logic, E...

1MB Sizes 0 Downloads 40 Views

Combining many-sortedlogic and object-oriented programming B M Kim*, K Y Ryu, S R Maeng and J W Cho

The logic' language based on many-sorted logic, EPOS, can support object-oriented concepts such as classes and inheritance. Classes can be treated as sorts and inheritance as many-sorted unification. However, there are some problems for supporting object-oriented programming, namely, the inconsistency in inheritance, difficult3' in exception handling, restricted inheritance hierarchy, etc. To soh,e these problems, we design an object-oriented many-sorted logic language T R Y and provide translation techniques by which a T R Y program is translated into an EPOS program.

Object-oriented programming has proven very useful in a number of important applications owing to its ability to unify and simplify the description of entities and their protocols. For example, in graphic applications windows, lines and composite structures can be represented as sets of objects that respond to a uniform set of messages. In the object-oriented programming paradigm, reality is represented in terms of entities, called objects, each with its associated set of procedures, called methods. An important feature of this paradigm is inheritance whereby an object is declared as a specialization of other objects, therefore inheriting their properties and methods. An action is then specified by passing a message to an object requesting the execution of one of its methods. An obvious approach to obtain the advantages of object-oriented programming is designing new languages based on object-oriented concepts j. An equally attractive approach from a practical viewpoint is designing extensions of existing systems to support the new paradigm. The feasibility of the second approach for Lisp 2-~ and Prolog 5-9 has been demonstrated. Structuring the universe of discourse is a successful method for human use in representing knowledge and in reasoning. Instead of using a single universe, we assume that the universe is divided into a number of subuniverses. Subuniverses may be contained in one another, may partially overlap or may be disjoint.

*Department of Computer Engineering,Kum-OhNational University of Technology, 188 Shin-PyungDong, Kumi, Kyung-Book730-701, Korea Computer Science Department and Center for Artificial Intelligence, Korea Advanced Institute of Science and Technology,Kusung-Dong 373-1, Yusung-Ku, Daejeon 305-701, Korea Vol 35 No 4 April 1993

Relations between subuniverses form a special kind of information, sometimes called taxonomic information, which helps to avoid meaningless or wrong conclusions. The benefits of using taxonomical information are widely recognized within the fields of knowledge representation ~° and ATP (Automated Theorem Proving). In particular, several proposals for extending Robinson's resolution calculus by sorts can be found ~' ,4 Applications of a many-sorted calculus to ATP challenge problems give an impressive demonstration of the calculus' potential for pruning search spaces ~5't6. In the context of logic programming, sorts offer a means for both data abstraction and more efficient computations. As an additional advantage, the associated proof-theoretic and model-theoretic properties can be straightforwardly adapted from ATP research. However, despite the many advantages of manysorted calculus, there has been little work ~v'~ on combining many-sorted logic and object-oriented programming. Since EPOS ~9is based on many-sorted logic, it has clear semantics, supports data abstraction and an inheritance mechanism, and offers enhanced language expressiveness resulting in shorter programs. Furthermore, EPOS allows efficient implementation by applying the highly developed implementation techniques for standard Prolog. For these reasons, in this paper we choose EPOS as a high-level target for supporting object-oriented programming and showing problems in supporting objectoriented programming. Also, in order to overcome these problems, an object-oriented many-sorted logic language TRY is designed and translation techniques by which a TRY program is translated into an EPOS program are provided. Our approach is distinguished from other approaches that combine logic- and object-oriented languages 5'7'~7 in that our approach is based on many-sorted logic and thus can support (multiple-) inheritance by using manysorted unification ~4. An executor of TRY can be implemented without extension of EPOS by translating a program in TRY into a program in EPOS. This distinguishes our approach from Prolog-XT ~ that is based on many-sorted logic. In the next section, the many-sorted logic language EPOS, which is the basis of our work, is described briefly. In the third section, object-oriented features of EPOS are examined and then problems in supporting object-oriented programming are described. In the

0950--5849/93/040241-13 © 1993 Butterworth-Heinemann Ltd

2,11

Combining many-sorted logic and object-oriented programming

fourth section, a new object-oriented logic language T R Y is suggested to overcome the problems described in the previous section. Implementation issues of T R Y are described in the penultimate section and, finally, concluding remarks follow.

MANY-SORTED PROLOG An extension of the Prolog language, EPOS 19, is based on many-sorted SLD-resolution introduced in Walther 14. It can support data abstraction and inheritance mechanisms and offer enhanced expressiveness resulting in shorter programs. Declarative semantics and related properties can be expressed within the framework of untyped definite clauses. Compared with Prolog, more efficient computations are obtained as inference on sorts is effected during unification rather than by resolution.

Language In the first-order predicate calculus, sorts are frequently used as an abbreviating notation. Formulas such as VX:tiger. cat(X) and 3X:vehicle. has(X, doors) are abbreviations for, respectively, VX. tiger(X)~cat(X) and ~X. vehicle(X)^has(X, doors). Thus certain unary predicates like tiger and vehicle are treated as sort symbols that denote a set of objects. A sort, say tiger, is a name for a set of objects, e.g. tiger = {tim, t o m , . . . } . Implications between sort symbols then correspond to set inclusion relations* on their sorts, i.e. tiger(X) ~cat(X) iff tiger < cat, and define a partial ordering on the sort symbols. EPOS is defined over an S-sorted signature E ( S ) = (F, P, SUBS), where S: a non-empty set of sort symbols,

F: a finite set of function (type-) declarations, P: a finite set of predicate (type-) declarations,

subsort of s2. It is assumed that the reflexive-transitive closure ~< of < defines a partial order on S. A type declaration for an n-ary predicate symbol p is denoted typeofp:si . . . . , sn where si ~ S, for 1 ~< i ~< n. A type declaration for an n-ary function symbol f has the form t y p e o f f.'sl . . . . . s n - > s where s, si e S, n/> 0. Nullary function symbols are called constants. Let Vs be an S-indexed family of mutually disjoint, countably infinite sets of variables. X:s is a type declaration for a variable X ~ V~. As the scope of a variable is limited to a single clause, the type declaration of a variable can only appear within a clause. A well-sorted term of type u is either a variable X ~ V,. with s ~< u or a term f ( t l . . . . , t,) for which there is a declaration typeoff:sl . . . . . s n - > s with s ~< u and every t~ is a well-sorted term of type s~. An atom P ( h . . . . . t~) is well-sorted iff there is a declaration typeofp:s~ . . . . . s~ and every t~ is a well-sorted term of type s~. A well-sorted clause or well-sorted goal contains only well-sorted atoms. A well-sorted program is a non-empty finite set of well-sorted clauses. Informally, type declarations define the greatest admissible sorts for arguments of functions and predicates. Well-sortedness is preserved for arguments with smaller sorts. Subsequently, it is assumed that there is exactly one type declaration for each function symbol and there is at least one constant of sort s for each s. For convenience, S is augmented by the least element 0 ¢ S, i.e. So = Swdp, that represents the empty sort, and it is assumed that the sort structure (So, ~<) is a complete lattice. For example, let us consider the following statements: (i) (ii) (iii) (iv) (v)

carnivores, mammals and aquatic are animals; cats are carnivores; whales are aquatics; whales and cats are mammals; moby and tim are instances of whales and cats, respectively; (vi) carnivores eat meat.

The statements are written in EPOS as shown in Figure 1. Sort symbols animal, carnivore, m a m m a l , aquatic, cat, and whale are used for representing animals, carnivores, mammals, aquatics, cats, and whales, respectively. Clauses (1)-(3), (4), (5), (6)-(7), (8)-(9), and (10) are the EPOS representations of statements (i), (ii), (iii), (iv), (v), (vi), respectively.

SUBS: a finite set of subsort declarations.

As usual, it is assumed that the corresponding alphabets of functions, predicates and sort symbols are pairwise disjoint. Multiple type declarations for a single function symbol are not allowed. A sort structure (S, ~<) is defined by a finite, nonempty set S of sort symbols and a finite set SUBS of subsort declarations s~ < s2 to be read as sort si is a

(1) (2) (3) (4) (5) (6) (7) (8) (9) (10)

*In EPOS, set inclusion relation is denoted by < instead of c.

Figure 1

242

carnivore < animal mammal < animal aquatic < animal cat < carnivore whale < aquatic whale < mammal cat < mammal typeof moby:whale typeof tim:whale eats(X:carnivore, meat)

Information and Software Technology

B M KIM, K Y RYU, S R MAENG AND J W CHO

Semantics The declarative semantics of many-sorted resolution can be captured by expressing sorted terms in the unsorted calculi. By using sort symbols as unary predicate symbols, the relations between functions and sort symbols as well as the subsort order can be represented by a set SAX(Y~) of unsorted clauses, called sort axioms. For a given sort signature E ( S ) = (F, P, SUBS), SAX(I~) is defined by

(a) s2(X):-st(X)ESAX(Y~) for every subsort declaration s~ < s, in SUBS; (b) s(f(X 1. . . . . 3(,)):-st (X~). . . . . s,,(X,,) ~ SAX(E) for every declaration typeof f : s t , . . . , s , - > s in F; (c) s(c)E SAX(E) for any constant c with sort s in S. For a well-sorted clause, say, likes(jane, X:male), its relativization likes(jane, X ) : - male(X)is the corresponding untyped version where the sort symbol male is used as a unary predicate symbol to express the sort of variable X. More generally, a sorted H o r n clause H : - G is translated into a relativization H ' : - G ' , s~(X~) . . . . . s,(X,), where Xi's are the variables of sort s~ that occur in H : - G , and H ' and G ' stand for the results of removing sort annotations for H and G, respectively. Figure 2 shows the relativizations of the clauses in Figure 1.

Inference rule For SLD-resolution, the main difference between the many-sorted and untyped calculus is located in the unification procedure: many-sorted unification has to preserve well-sortedness. A well-sorted substitution a = { X ~ t ~ , . • .,Xk*--t~} has the property that sort(ti) ~< sort(Xi) for all i where sort(X) means the sort of term X. A well-sorted unifier of terms tl and t~ is a well-sorted substitution a such that o ( t l ) = a(fi). In order to preserve the completeness of many-sorted resolution, it is necessary to unify variables X and Y in the case where sort(Y) and sort(X) are not comparable, but do have a c o m m o n subsort s e S that s ~< sort(X) and s ~< sort(Y). This case is covered by a so-called weakening substitution ~o = {X~-Z, Y ~ Z } which replaces X and Y by a new variable Z of sort s. However, the most general weakening substitution does not exist under a general partially ordered sort hierarchy 16. For example, let a query ' : - has_wing(X:e).' be given on the program in Figure 3. To solve the query, we must find the most (1') (23 (3') (4') (5') (6') (7') (8') (9') (10')

animal(X): - carnivore(X) animal(X): - mammal(X) animal(X): - aquatic(X) carnivore(X):- cat(X) aquatic(X): - whale(X) mammal(X): - whale(X) mammal(X): - cat(X) whale(moby) whale(tim) eats(X, meat): - carnivore(X)

Figure 2 Vol 35 No 4 April 1993

/* sorts r, b, 1 and e denote reptiles, birds, animals with lungs and animals which lay eggs, respectively */ r
Figure 3 general weakening substitutions for {X:e, Y:I}. We can have weakening substitutions {X,-Z:I,Y*--Z:I} and {X,-Z:b, Y , - Z : b } . But there is no most general weakening substitution for them and thus the query fails. As a consequence, the many-sorted calculus can be refutation incomplete because the unsorted version of the query on the unsorted version of the program in Figure 3 succeeds. To solve this problem, Walther uses complete and minimal set of well-sorted unifiers, which concept is borrowed from unification under equational theories ~6. The algorithm for complete and minimal set of wellsorted unifiers is described ~4'16.In the above example, for an instance, {{X~Z:I, Y.--Z:I}, { X ~ Z : b , Y ~ Z : b } } is a minimal and complete set of well-sorted unifiers for {has_wing(X:e), has_wing(Y:l)}. Using complete and minimal sets of unifiers makes the control mechanism complex and lessens the advantages of many-sorted logic because the cardinality of a complete and minimal set of well-sorted unifiers can be greater than 1 and thus more than one resolvents for a given pair of clauses and literals resolved upon can be generated. For efficiency EPOS allows only the sort structures under which the complete and minimal set of unifiers of any two terms is a singleton, that is. only a semi-lattice is allowed. The basic unification step is illustrated in Figure 4. The rest of the unification algorithm is the same as the unsorted (untyped) case.

OBJECT-ORIENTED PROGRAMMING IN MANY-SORTED PROLOG As our goal is to combine many-sorted logic and objectoriented programming, we have to check what has been gained by incorporating EPOS with OOP (objectoriented programming) and what has still to be added to obtain a useful system. basic_unify(X, t): /* many-sorted unification of a variable X and a well-sorted term t. The function glb computes the greatest lower bound of two sort symbols in S for given sort structure (So, ~<). */ (i) if t is not a variable and sort(t)~
Figure 4 243

Combining many-sorted logic and object-oriented programming

Object-oriented features in many-sorted Prolog Classes and instances EPOS has a concept of sort which corresponds to type in most computer languages including C O M M O N LISP and CLOS 3. A sort is a name for a set of objects. In EPOS an object can be a member of more than one sort, because two sets can overlap and the sets can have subsets. Sorts are useful for organizing and classifying objects, and in some cases for compiler optimization. Classes are useful in the same way, so we want to treat classes as sorts in this paper. However, there are some differences in classes and sorts: sorts do not have concepts such as instance variables, methods, messages and inheritance. Now, we will examine how the differences are covered in many-sorted logic frameworks. All instances of a particular class are similar in structure. They all have the same number of instance variables and the same set of instance variable names. Each instance has its own states, which have their own contents. In EPOS, an instance variable can be represented as a unit clause, var(inst, val), where vat is the name of instance variable, inst is the name of an instance, and val is a value of the appropriate type, meaning that val is the value associated with the instance variable vat in the instance denoted by inst. The methods of an instance are the operations that the instance can perform. They specify what messages they accept and what actions they perform when they receive such messages. In EPOS a method can be represented as a set of clauses. For example, suppose that the class reg~poly with perimeter and what_is_it as its associated methods is declared in SmallTalk style as in Figure 5. To represent this class in EPOS, the class name reg_poly is mapped to the sort symbol reg_poly and the methods perimeter and what_is_it can be mapped to the following many-sorted Horn-clauses: perimeter(lnst:reg_poly, N, L, P ) : - P is N * L what_isJt(Inst:reg_poly, a_reg_poly)

Messages In the object-oriented programming paradigm, an action is specified by passing a message to an object requesting the execution of one of its methods. An object can send a message to any object as long as it knows the address of the target object. In SmallTalk, the method perimeter defined in Figure 5 may be executed by sending the !

Reg_poly Subclass: # Object instanceVariableName: " classVariableName: " poolDictionary: "

!

perimeter: N with: L IPl P ~= N , L !

P

what._isit 'a_reg_poly'

Figure 5 244

message 'perimeter 2 with: 3' to an object of the class Reg_Poly as follows: P = (Reg_poly new) perimeter: 2 with: 3 In EPOS, sending a message is specified by a subgoal as follows: perimeter( :reg_poly, 2, 3, P) Because message sending is treated as subgoal proving in EPOS, a failure after the success of message sending causes backtracking to the message sending subgoal. By this backtracking mechanism, alternative solutions can be obtained.

Inheritance Classes and the relation between superclasses and subclasses (shortly, super-sub relation) in OOP correspond to sorts and the set inclusion relation in many-sorted logic, respectively. Consequently, the inheritance hierarchy corresponds to the sort hierarchy. Now we will show how the inheritance mechanism can be supported in EPOS. We suppose that the following method is defined in a class A which is a superclass of a class B: write_head(OBJECT:a, [HIT]): - write(H) Because a message can be considered as an expanded subgoal (or predicate) with a class-defining argument, the message 'write_head([bmkim, kyryu])' sent to an instance inst I of the class B can be treated as the subgoal represented as follows: write head(instl:b, [bmkim, kyryu]) prove this subgoal, it is checked that write_ head(inst l:b, [brnkirn, kyryu]) and write-head(OBJECT:a, [HI T]) are unifiable. Seeing that there is a complete and

To

minimal set of unifiers ~ = {{OBJECT:a*--instl:b, H,-bmkim, T,---[kyryu]}}, these two predicates are unifiable and write(bmkirn)is executed. Suppose, also, that the message 'write_head ([bmkim, kyryu])' is sent to an instance inst2 of the class C which is neither a subclass nor a superclass of A. To handle this message, it is checked that the subgoal write_head(inst2:c, [bmkirn, kyryu]) can be unified with write-head(OBJECT:a, [HI T]). However, these are not unifiable because sorts c and a have no common subsort. Thus, this message sending is treated as a failure, that is, the class C does not inherit the method write_head in the class A.

Weakness of many-sorted Prolog in supporting OOP We have examined how the concepts such as instance variables, methods, messages and inheritance can be treated in many-sorted frameworks, especially in EPOS. Instance variables and methods are represented as clauses, and both are accessed as goals; messages are treated as (sub-) goal proving, and inheritance as many-

Information and Software Technology

B M KIM, K Y RYU, S R MAENG AND J W CHO

sorted unification. However, these are not enough to support object-oriented programming, i.e., something should be added to overcome the following problems. Problem 1. A change to the value of an instance variable can be realized as a side effect to the EPOS database, but such a change is not recovered when backtracking occurs. For example, let count be an instance variable of a which is an instance of class ca and the method m I be defined as follows: ml(X:ca, Y):-count(X, Z), NZ is Z + 1, update(X, count, NZ), g(Y) update(Inst, X, Y):- Old_State =..[X, Inst, Z], retract(Old_State) New_State =..[X, Inst, Y], assert(New_State) Suppose that a message 'ml(4)' is sent to a. Then, this message is treated as a subgoal ml(a:ca, 4)and it is unified with the ml(X:ca, Y) and thus the body of the clause m 1 is executed. Now, suppose that the subgoal g(4) fails during the execution of the body of m 1. Then, the message subgoal ml(a:ca, 4)also fails. Though we want to make a state of an instance unchanged when a message goal fails, the state of a is changed, i.e. the value of instance variable count is incremented by 1 when the method m 1 fails. Problem 2. Logical inconsistency can occur if the destination object of a message is not mentioned explicitly. For example, we suppose that C is a subclass of the classes A and B and that a method is defined as follows:

Problem 3. Inheritance can conflict if two superclasses might both supply methods with the same name. These inheritance conflicts can be resolved by defining an order of precedence that determines which class's characteristics dominate. Ordering of classes is partially determined by the super-sub relation. Since classes are considered as sort~ this ordering can be considered as a partial ordering on sorts. However, ordering of classes is not always preserved because of the linear search mechanism of EPOS. For example, let a class labeled_ window be a subclass of a class window and let a method move be defined in each class as in Figure 6. Suppose that a message 'move(2,3)' is sent to lwindow which is an instance of labeled_window. This message can be considered as a subgoal move(lwindow:labeled window,2,3) and it can be unified with the first move in Figure 6 according to the search mechanism of EPOS. That is, the method move defined in window class is executed. This violates the principle that a subclass is more specific than a superclass and thus a method in a subclass has higher precedence than a method in a superclass. Problem 4. All existing OOP systems which have practical applications provide some way to represent exceptions of general statements about the world being described. In EPOS, it is difficult to represent exceptions because there is no way to describe the sorts that arise from the use of exceptions. Suppose, for example, that we have formulas that define a taxonomic hierarchy as follows:

calculate_area(OBJECT:b, X, Y, Z ) : - Z is X • Y Now, suppose the message 'calculate_area(2, 3, Z)' is sent to any object of the class A. Then A inherits the method calculate_area from the class B since this message sending corresponds to the proving of subgoal calculate-area(Object:a, 2, 3, Z) and this subgoal is unified with calculate_area(Object:b, X, Y, Z). This is contradictory to that A cannot inherit methods of B because A is not a subclass of B. move(Inst:window, X, Y ) : - x(Inst, DX), y(Inst, DY), NX is DX + X, NY is DY + Y, update(Inst, x, NX), update(tnst, y, NY). move(Inst:labeled_window, X, Y ) : x(Inst, DX), y(Inst, DY), labeLx(Inst, LX), label_y(Inst, LY), NX is DX + X, NY is DY + Y, LNX is LX + X, LNY is LY + Y, update(Inst, x, NX), update(Inst, y, NY), update(Inst, label_x, LNX), update(Inst, label_y, LNY).

Figure 6 Vol 35 No 4 April 1993

bird(X),-canary(X) bird(X),--ostrich(X) Suppose we also have statements that describe some of the properties of the objects in the taxonomic hierarchy. For example, suppose we want to say that all birds except ostriches can fly, that all birds have wings and lungs, that all canaries sing and are yellow, and that all ostriches have long and thin legs. One way to do this is with the following unsorted first-order formulas: can~fly(X)~bird(X), ~ostrich(X).--(*) has_wings(X) ~ bird(X). has_lungs(X) ~ bird(X). is_yellow(X) ~ canary(X). sings(X) ~ canary(X). has_long_thin_legs(X)*-- ostrich(X). Now, let us represent these formulas by EPOS's formulas. The taxonomic hierarchy corresponds to the subsort relation (subclass relation), i.e. the taxonomic hierarchy is represented as follows: sort canary < bird, ostrich < bird. Other formulas except the formula marked by * are represented as follows: has_wings(X:bird) has_lungs(X:bird) 245

Combining many-sorted logic and object-oriented programming is_yellow(X:canary) sings(X:canary) has_long_thin_legs(X:ostrich)

Problem 5. To simplify the control mechanism, EPOS assumes that a given sort hierarchy is a complete lattice. However, this assumption seems to be unnatural or unintuitive. Let us consider the following statements ~6. (i) reptiles and birds are animals, which breath by lungs and lay eggs; (ii) there are reptiles as well as birds; (iii) each animal with lungs and wings has feathers; (iv) all animals without wings are poikilothermic, provided they lay eggs. Then we can express the statements in the style of EPOS as follows: reptile reptile bird < bird <

< animal_with_lungs < animal_lay_eggs animal_with_lungs animaLlay_eggs

f(X:animaLwith_lungs): - w(X:animaLwith_lungs) p(X:animal_lay_eggs): - not(w(X:animaLlay_eggs)) sorts reptile, bird, animal_with_lungs, anim a l H a y ~ g g s denote reptiles, birds, animals with lungs and animals which lay eggs, respectively. The predicates where

w(X)--animal X has wings f(X)--animal X has feathers p(X)--animal X is poikilothermic are used as abbreviations. However, the above program cannot be allowed in EPOS because the sort hierarchy is not a complete lattice. Thus, to express the above statements in EPOS, the user should introduce a new dummy sort as follows: r_or_b < animaLwith_lungs r_or_b < animaLlay_eggs reptile < r_or_b bird < r_or_b The approach that the user invents dummy sorts to make the sort hierarchy to be a complete lattice is endurable for a simple case, but the approach overburdens the user for a complicated case.

A HIGHER-LEVEL SOLUTION

LANGUAGE

As shown in the previous section, EPOS can support the salient features of object oriented programming, but it has some problems in supporting object-oriented programming such as the inconsistency in inheritance, difficulty in dealing with exceptions, restricted inheritance hierarchy, and so forth. To overcome these prob246

lems, we define a higher-level language, called TRY, in which the problems are attacked as follows: (1) To maintain the state of an object consistently (i.e. to overcome Problem 1), a backtractable database predicate is introduced. (2) To avoid Problem 2, user should specify the destination of a message sending. (3) To eliminate the anomaly of inheritance (i.e. to overcome Problem 3), methods are rearranged according to their precedences so that a method with higher precedence is located in front of a method with lower precedence. (4) To overcome Problem 4, an exclusion mechanism is supported. (5) To overcome Problem 5, a partially ordered inheritance hierarchy is allowed.

C l a s s e s and objects A class in TRY is defined basically by a 3-tuple which consists of superclass declarations, instance variable declarations, and method definitions.

Superclass declarations The declarations of superclasses begin with the keyword super followed by superclasses. In EPOS, it is assumed that the inheritance hierarchy is a complete lattice. But, in TRY, a partially ordered inheritance hierarchy is allowed, i.e. two classes (or sorts) can have more than one common subclass (or subsort). Since two superclasses might both supply methods with the same name, inherited methods may conflict with each other. TRY resolves this conflict by defining an order of precedence on superclasses. Classes are totally ordered by the ordering rule which is described below under the heading 'Inheritance'. Instance variable declarations Instance variables are private memory maintaining the internal state of each object of that class. Instance variable declarations begin with the keyword state followed by a list of unit clauses such that their names are identifiers of instance variables and their arguments are values of instance variables. For example, let the instance variables of class person consist of age, sex, and salary with default values 0, male, and 0, respectively. Then the instance variables of person are declared as follows: state age(0), sex(male), salary(0); The value of an instance variable can be changed only by two predicates, i.e., bupdate(Inst_Var_Name, New Value) and nupdate(InsLVar_Name, New_Value). These predicates are the same except that bupdate is backtrackable. Since bupdate is backtrackable, the state of an instance is not affected by failure in solving message goals. For example, let c o u n t ~ u m be an Information and Software Technology

B M KIM, K Y RYU, S R MAENG AND J W CHO

instance variable of some class. Then, incrementing the instance variable by 1 may be programmed as count_num(X), X = X + 1, bupdate(count_num, X). Method definitions A method comprises the active properties of an instance, as distinguished from the structure superclass part, and instance variable part), the passive properties. A method operates on an instance by calling built-in predicates which are same as those of EPOS, accessing its own instance variables, and passing messages to other instances. A method is defined as follows: method methodJlame option with

method_clausel

{defclass person state name(_), age(_), sex(_), income(_), birthday(_); method prinLpersonality with print_personality0 : - name(X), write(X) . . . . . birthday(Y), write(Y). end;

} Figure 8 identifier is bound. Each initialization argument has the form name(value), where name is the name of the variable and value is its initial value. For example, suppose that a class person is defined as shown in Figure 8. Then a sample object could be created by create_object (per-

son,[name(bmkim), age(27), birthday(1964.8.24)],

Obj).

method_clause. end where method_clausej ...method_clause, are Hornclauses whose heads have the same name and arity. When a method is called, the first clause in the method is tried. If this fails, the next clause is tried and so forth. If the last clause fails, the method call itself fails. However, if the method is defined with the option :continue, methods in superclasses are called until a method call succeeds or there is no superclass which contains that method. The :continue option combined with the fail predicate can provide method composition. For example, suppose that the classes bounded_buffer and buffer are defined as in Figure 7. Then the method put in bounded_buffer is a composition of the put methods defined in boundedJbuffer and buffer.

Instance creation A new object is created by the predicate create_object which takes three arguments: its class, a list of its initialization arguments, and the variable to which its {defclass buffer state buf(X); method get with get(_):- bur([]),!, fail. get(H) : - buff[HIT]), nupdate(buf, T). end; method put with put(T) : - bur(X), append([T], X, NB), nupdate(buf, NB). end;

}

{defclass bounded_buffer state bound(Max), count(Num); super buffer; method put :continue with put(T) : - bound(Max), count(Max), !, fail. put(T) :-- count(Num), New_Num is Num + 1, nupdate(count, New_Num), fail. end;

}

Figure 7 Vol 35 No 4 April 1993

Message sending The application of methods to instances is specified using the infix operator ' < - - ' as follows: reg_poly < -perimeter(6, 10, X). Message sending using the infix operator ' < - - ' is backtrackable if the failure occurs after message sending. A new type of message sending using the infix operator ' < i - - ' is also provided, which never backtracks to the message sending subgoal if the message sending is executed successfully. That is, the success of the predicates commits the execution as the commit operator does in concurrent Prolog 2°. To avoid Problem 2 as described above, the destination of message sending, i.e. the left-hand side o f ' < - ' (or '<~ - ' ) , must be bound to an atom. If the destination is not bound to an atom, correctness of program is not guaranteed and thus a wrong solution may be obtained. An instance can execute a method in itself by sending a message to itself, denoted by built-in symbol self.

Inheritance Method (or Instance Variable) Inheritance Each class defines some methods (or instance variables) and inherits all the methods (or instance variables) of the superclasses. If the method (or instance variable) names inherited from the superclasses are disjoint, there is no problem. On the other hand, if there are two or more methods (or instance variables) with the same name, inherited methods (or instance variables) can conflict. For example, two superclasses might both supply methods with the same name. A conflict can also occur between a class and one of its superclasses. TRY resolves inheritance conflicts by defining an order of precedence that determines which class's method (or instance variable) dominates. 247

Combining many-sorted logic and object-oriented programming The order of precedence between classes is determined by the following rules:

bounded_buffer < buffer

(a) a subclass is more specific than a superclass and thus the subclass has a higher precedence; (b) when two classes are not ordered by the super-sub relation, they are ordered textually, that is, a class c] has a higher precedence than a class c2 if Cl is defined before c2 in the text.

put(Inst:bounded_buffer, _): - bound(Inst, Max), count(Inst, Num), Num = Max, !, fail put(Inst:bounded_buffer, _): - count(Inst, Num), New_Num is Num + 1, nupdate (Inst, count, New_Num), fail get(Inst:buffer,_) : - buf(Inst, []), !, fail get(Inst:buffer, H) : - buf(Inst, [HIT]), nupdate(Inst, T)I get(Inst:buffer,_) : - !, fail put(Inst:buffer, T) : - buf(Inst, X), append([T], X, NB)I nupdate(Inst, buf, NB) put(Inst:buffer, ) : - !, fail

Exclusion Exclusion is declared by explicitly mentioning methods or instance variables with the following syntax: exclude method_or_inst L from superclassj,...,

state(buffer, [buf(X)]) state(bounded_buffer, [buf(X), bound(MAX), count(Num)]

Figure 10 and method_or_inst, from superclass,,

which means that method_or_insti, l <~i <~n, is not inherited from the superclass superclassj. The example in Problem 4 can be programmed in T R Y as shown in Figure 9.

TRANSLATING TRY TO EPOS If a TRY program satisfies the rules of syntax, a TRY program is translated into an EPOS program. A TRY program is translated into the extended EPOS program which contains new features that EPOS does not support such as expressive sort symbols and partially ordered sort hierarchy. Then, the extended EPOS program is translated into an EPOS program.

{defclass bird method can_fly with ca~fly(). end; method has_wings with has_wings(). end; method has_lungs with has_lungs(). end;

}

{defclass canary super bird; method is-yellow with is_yellow(). end; method sings with signs(). end;

}

{defclass ostrich super bird; exclude can_fly from bird; method has_long_thir~legs with has_long_thin__legs(). end;

}

Figure 9 248

Translating TRY to extended EPOS Classes and instance Because we want to use the sort hierarchy for inheriiance in object-oriented programming, classes in TRY are treated as sorts in EPOS. Thus a class name is translated into a sort symbol and the super-sub relation into the subsort relation. The instance variables of a class, including inherited variables, are translated into the following state unit clause:

state(classname, [state_clause] . . . . . state_clause.I). A method is translated into a set of many-sorted Horn clauses as follows: a class-defining argument is inserted into the head of each clause for a method and a dummy clause (i.e. clause_name:-!, fail) is added after the last clause for the method when the method is declared without the :continue option. (Note that, in TRY, failure of the last clause for a method is treated as failure of the method itself when the method is not declared with the :continue option.) For example, let us consider the program in Figure 7. Since the get method is declared without the continue: option, a dummy clause is added as shown in Figure 10. However, for the put method in bounded_buffer, no dummy clause is added because it is declared with the :continue option. The built-in predicates of EPOS are translated into themselves and a predicate accessing an instance variable is translated into the form that the class-defining argument is inserted as its first argument. For example, the predicate buf([HIT]) in Figure 7 is translated into buf(Inst, [H]T]) as shown in Figure 10. The predicates bupdate/2 and nupdate[2 are translated into bupdate[3 and nupdate/3, respectively. For example, the nupdate(buf, NB) predicate in Figure 7 is translated into nupdate(Inst, buf, NB), where Inst is a classdefining argument. The bupdate/3 and nupdate/3 are implemented as follows: bupdate(Inst, X, Y) : - O l d = . . [X, Inst, T], call(Old) New =..IX, Inst, Y], bupdatel (Old, New) Information and Software Technology

B M KIM, K Y RYU, S R MAENG AND J W CHO

sex(person 1:person, _) income(person 1:person, _) birthday(person I :person, (1964, 8, 24))

bupdatel(Old, New):- retract(Old), assert(New) bupdatel(OId, New):-retract(New), assert(Old), fail nupdate(Inst, X, Y) : - O l d =..[X, Inst, _], retract(Old) New =..[IX, Inst, Y], assert(New)

Message sending where the first argument is an instance name, the second argument an instance variable name and the third argument its new value.

Message sending corresponds to the execution of a Prolog goal. Thus, the messages (a) and (b) below are translated to (a') and (b'), respectively.

Instance creation The create_object/3 predicate is translated into itself. Instance creation is explained in terms of generating a constant whose sort corresponds to the class o f instance and asserting instance variables which can be represented by unit clauses. Thus, create_object]3 can be realized as follows: create_object(CLASS, INIARGS, OBJ) : - gensym(CLASS, OBJ), state(CLASS, States), create_state_variables (States, OBJ), initialize(INIARGS, OBJ)

(a) . . . . Inst < -perimeter(6, 10, X),. (b) . . . . Inst ,~ -perimeter(6, 10, X),. (a') . . . . perimeter(Inst, 6, !0, X). . . . (b') . . . . perimeter(Inst, 6, 10, X), !,.. When the destination of a message is sell self is replaced with the source of message sending. For example, suppose that the library class is defined as follows: {defclass library method append with append([ ], L, L) append([HIT], L, [HIL 1]): - self < - append(T, L, L l) end

create_state_variables([ ], OBJ). create_state_variables([HIT], OBJ): - H =..[P, A], or S =..[P, OBJ, A], assert(S), create_state_variables(T, OBJ) initialize([ ]). initialize([HIT], OBJ):-H =..[P, A], nupdate(P, A, OBJ), or initialize(T) Where the predicate create~tate_variables(St, Ob) asserts a clause of the form att(Ob, Val) corresponding to each element att(Val) in St, For example, let us create an object of class person as defined in Figure 8. Then, the constant person l is generated by gensym predicate and the following clauses are asserted;

name(person I :person, bmkim) age(person l :person, 27)

}

Then, the above program in TRY is translated into the following EPOS program: append(Inst:library, [ ], L, L) append(Inst;library, [HIT], L, [HILl]):append(Inst:library, T, L, L1)

Inheritance Many-sorted unification plus the search mechanism in Prolog well supports linear order inheritance by rearranging methods with the same name in a total order that reflects the two local orderings in the previous

{defclass parallelogram

{defclass reg_poly

method area with area(Base, Height, A) : - A is Base, Height. end. method whatAs_it with what_is_it(a-_parallelogram). end.

method perimeter with perimeter(N, L, P) : - P is N • L. end. method what_is__it with whaLis_it (a_reg_polygon). end.

{defclass rhombic super parallelogram

{defclass rectangle super parallelogram;

method whatAs_it with what_is_it(a_rhombic). end.

method what_is__it with whatis_it(a_rectangle). end.

{defclass square Super rhombic, rectangle, reg_poly;

{defclass pentagon super reg__poly;

method what_is_it with what__is__it(a_square). end.

method what_is_it with whatis_it(a_pentagon). end.

}

}

}

}

}

}

Figure 11 Vol 35 No 4 April 1993

249

Combining many-sorted logic and object-oriented programming

section. For example, suppose objects are defined as in Figure 11. Then, we can find a precedence ordering parallelogram < p rectangle < p reg_poly < p rhombic < p pentagon < p square

which reflects the textual order and the super-sub relation between classes, where C~ < pC2 means that C2 has the higher precedence than C~. Thus the program in Figure 11 is translated as shown in Figure 12. If the message area(3,5,X) is sent to an instance s q l of the class square then it is compiled as follows: . . . . area(sql:square, 3, 5, X) . . . . This (sub-)goal is unified with area(InstTarallelogram, Base, Height, A ) and the goal body is executed and thus X - 15 is returned. That is, s q l inherits the method area from the class parallelogram. Exceptions are translated into complemented objects. Let class Co be a superclass of classes C~ . . . . . and Cm, which are defined as follows: {defclass Co method m~ with mi(. . .):-bodyl

}

m,'(. . .):-body. end;

{defclass Cl exclude m I from Co;

{defclass Cm exclude m I from Co;

rhombic < parallelogram square < rhombic square < rectangle square < reg_poly rectangle < parallelogram pentagon < reg_poly what__is_it(Inst:square, a_square) what__is_it(_:square, _) : - !, fail what_is_it(Inst:pentagon, a_pentagon) what-is_it(_:pentagon, _) : - !, fail what__is__it(Inst:rhombic, a_rhombic) what_is_it(_:rhombic, _) : - !, fail perimeter(Inst:reg__poly, N, L, P) : - P is N • L perimeter(_:reg_poly. . . . . . ) : - !, fail what_is_it (Inst:reg__poly, a_reg__polygon) what_is_it(_:reg_poly, _) : - !, fail what_is__it(Inst:rectangle, a-rectangle) what_is_it(_:rectangle, _) : - !, fail area(Inst:parallelogram, Base, Height, A) : - A is Base • Height area(_:parallelogram . . . . . . ) : - !, fail what_-is_it(Inst:parallelogram, a-_parallelogram) what_is-it(_:parallelogram, _) : - !, fail Figure 12

250

canary < bird ostrich < bird is_yellow(_:canary) sings(_:canary) has_long_thin(_:ostrich) car~ly(_:bird\ost rich) has_wings(_:bird) has_lungs(_:bird) Figure 13

Then a method rn~ in class Co is translated as follows: ml (-:c0 \(cl + ' " + Cm). . . . ): -- bodyl m.(-:Co\(Cl + " "

+ Cm) . . . .

):--body n

where st \s2 and s~ + s2 are a complement sort symbol and a disjunctive sort symbol, respectively. Let S~ and S: be sets of objects denoted by sorts s~ and s2, respectively. Then, sort Sl \s2 denotes a set of t's such that t e S~ and t ¢ $2, and sort s~ + s2 denotes a set of t's such that t e S~ or t ~ S2. By applying the transformation rule to the TRY" program in Figure 9, the method can_fly in class bird is translated into can_fly(_:bird\ostrich)as shown in Figure 13.

Translating extended EPOS to EPOS A TRY program is translated into an extended EPOS program by the translation rules in the previous section. An extended EPOS program contains new features that EPOS does not support such as expressive sort symbols (i.e. complement sort symbols and disjunctive sort symbols) and partially ordered sort hierarchy. Extended EPOS can be supported by extending the unification algorithm and control mechanism of EPOS. However, this approach can not derive as much advantage as desired because:

(i) supporting expressive sorts in unification level makes unification complex and thus run-time overhead is increased; and (ii) when a partially ordered sort hierarchy is allowed, a complete and minimal set of unifiers between two terms can be arbitrarily large (although always finite, if the set of sort symbols is finite) ~6. This can make the control mechanism of Prolog complex. To overcome these problems, we translate an extended EPOS program into an EPOS program by use of simple technical remedies: (i) an expressive sort symbol is replaced by an equival~ ent simple sort symbol (the detail is described in the~ next section); and (ii) the given sort hierarchy is translated into a meet~ semilattice by invention of additional sorts (the detail is also described in the next section). Information and Software Technology

B M KIM, K Y RYU, S R MAENG AND J W CHO

canary < bird~aoLostrich bird_noLostrich < bird ostrich < bird is_yellow(_:canary) sings(_:canary) has_long__thin(_:ostrich) can__fly(_:bird_not_ostrich) has-_wings(_:bird) has_lungs(_:bird)

D E A B C

D

E

A

B

C

0 0 0 1 1

0 0 1 1 1

0 0 0 0 0

0 0 0 0 0

0 0 0 0 0

Table 2. The greater than relation

Figure 14 For example, the program in Figure 13 is translated into the program in Figure 14. More generally, an extended EPOS program is translated into an EPOS program by converting a sort structure with expressive sort symbols and partially ordered sort hierarchy into a sort structure which has only simple sort symbols and whose sort hierarchy is meet_semilattice, and replacing non-simple sort symbols with unique (simple) sort symbols. Conversion

Table 1. The immediately greater than relation

of sort structure

The main procedure is translating an extended EPOS p r o g r a m into an EPOS program is to convert the sort atructure. In this section, we will describe the converting procedure. Given a sort structure (S, ~<), the mlb (maximal elements of the lower bounds) of s l • S and s 2 • S , denoted by mlb(s~,s2), means the set of all maximal elements a m o n g the lower bounds of s~ and s2. That is, mlb(sj, s2) = max(lbs(sl, s2)),

lbs(sL,s:)= {s e Slsl >~s AS2 ~>S}, and max(S) = {s e S](Vt ~ S)s ~ t}. F o r example, mlb(A, B) = {C, D} and mlb(C, D) = {E} for the sort hierarchy such that E < C, E < D, C < A, C
Figure 15. The transformation procedure Vol 35 No 4 April 1993

D E A B C

D

E

A

B

C

I 0 0 1 1

0 1 1 1 1

0 0 1 0 0

0 0 0 l 0

0 0 0 0 1

symbols into a meet-semilattice with simple sort symbols by introducing a new sort symbol called internal sort symbol for each mlb(s~, s2) such that its cardinality is greater than 1. The procedure is shown in Figure 15. To calculate the mlb for each pair of sort symbols the procedure in Figure 15 uses the greater than relation which shows both supersorts and subsorts of sort symbols. The greater than relation between simple sorts can be calculated easily from the information declared in the sort declaration part. The greater than relation between simple sort symbols is constructed from the reflexive and transitive closure of the immediately greater than relation. The immediately greater than relation shows both immediate supersorts and immediate subsorts of sort symbols. Given an n x n boolean array M, its reflexive and transitive closure M * is given by: n

M* = i=~=oMi where the power operation is computed as matrix multiplications in the boolean ring of n × n bit-matrices. Let us consider the sort hierarchy such that D < B, D < C , E < A , E < B , and E < C . The immediately greater than relation defined by this ordering can be represented by an array as shown in Table 1. Each row contains l's only in those columns headed by elements which are immediately less than the element heading the row; and it contains O's otherwise. Similarly, each column contains l's only in those rows headed by the elements which are immediately greater than the element heading the column. By applying the above equation to the matrix in Table 1, its reflexive and transitive closure

D

E

Figure 16 251

Combining many-sorted logic and object-oriented programming

D E A B C B\D

D

E

A

B

C

B\D

I 0 0 1 1 0

0 1 1 1 1 1

0 0 1 0 0 0

0 0 0 1 0 0

0 0 0 0 1 0

0 0 0 1 0 1

C

B

A

Table 3. The greater than relation

r

Table 4. The mlb-matrix

C B\D {D} {} {E} {E} {E} {E} {D,E} {B\D}

D

E

A

B

D E A B

{D} {} {} {D}

{} {E} {E} {E}

{} {E} {A} {E}

{D} {E} {E} {B}

C

{D}

{E}

{E}

{D,E}

{C}

{E}

B\D

{}

{E}

{E}

{B\D}

{E}

{B\D}

can be obtained as shown in Table 2 and represented as in Figure 16. However, in the case that expressive sorts are involved, it is not easy to calculate the greater than relation. To calculate the greater than relation between sort symbols including expressive sort symbols, we use two functions f and g. The function f maps a sort structure to a set of logical formulas: a subsort relation s, < s 2 is converted to a logical formula Sl~S2. The function g directly converts a sort symbol to logical formulas, i.e., + is mapped to v (logical or) and translating of \ introduces ^ (logical and) as well as (logical not). For example, the expressive sort symbol a\(b + c) is converted to a A -,~(b v c). Let (S, -%<)be a given sort structure, st and s2 be sort symbols in S, f be a function which converts a sort hierarchy to a set of logical formulas, and g be a function which converts a sort symbol to a logical formula. Then the greater than relation between sort symbols is governed by the rules as follows: st < S2ifff(S)[-g(st)'-*g(s2),

Figure 18 structure and an internal sort symbol I be st + ' • ' + s,, where s, e S. Then the greater than relation for / is defined as follows: I ~~s for some s,, and I>~I. Suppose that the sorts A, B, C, D, and E are given such that D < B , D < C , E < A , E < B , and E < C , and a non-simple sort symbol B\D is used in an extended EPOS program. Then the greater than relation of the given sort hierarchy is calculated as shown in Table 3 and the mlb-matrix which is an n × n array representing the mlb for each pair of sort symbols is calculated as shown in Table 4. Figure 17 shows the greater than relation as a diagram. Let us consider the mlb-matrix in Table 4. Because the mlb of two sort symbols B and C is not a singleton, we know that the sort hierarchy given in the above example is not a meet-semilattice. To transform this sort hierarchy to a meet-semilattice, an internal sort symbol I is introduced, and the greater than relation in Table 3 is extended to the one in Table 5. Figure 18 shows the extended greater than relation as a diagram. Table 5. The extended greater than relation

which means that st is a subsort of s2 if and only if g(st)-~g(s2) is logically derivable from f(S). Since internal sort symbols are introduced during the conversion of the sort structure, it is necessary to calculate the greater than relation between internal sort symbols and other sort symbols. Let (S, <~) be a sort A

D

E

B

C

D

E

A

B

C

B\D

I

1 0 0 1 1 0 1

0 1 1 1 1 1 1

0 0 1 0 0 0 0

0 0 0 1 0 0 0

0 0 0 0 1 0 0

0 0 0 1 0 1 0

0 0 0 1 i 0 1

D E A B C B\D I

Table 6. The extended mlb-matrix

D

Figure 17 252

E

D

E

A

B

C

B\D

I

(D} {} {} {D} {D}

{/ {E} {E} {E} {E}

{} {E} {A} {E} (E)

{D} {E} {E} {B} {I}

{D / {E} {E} {I} {C}

{} {E} {E} {a\O} {E}

{D} (E) {V} {I} {I}

B\D

{}

{E}

{E} {B\D} {E} {B\D} {E}

I

{D}

{E}

{E}

D E A B C

{I}

{I}

{E}

{I}

Information and Software Technology

B M KIM, K Y RYU, S R MAENG AND J W CHO

A

B

C

program instead of extending EPOS. This distinguishes our approach from other approaches, e.g. L O G I N 17and Prolog-XT ~8, to combine logic- and object-oriented language.

REFERENCES

E

D

Figure 19

Using the extended greater than relation, mlbs of I and other sort symbols are calculated and thus the mlbmatrix in Table 4 is extended to the one in Table 6. As there is no pair of sort symbols such that the cardinality of its mlb is greater than 1 in the extended mlb-matrix, immediated subsorts and supersorts of internal sort symbol ! and non-simple sort symbol B\D are calculated and the expressive sort symbol B\D is replaced by a new internal sort symbol J. Consequently, the given sort hierarchy is converted as in Figure 19.

CONCLUSIONS In the view of EPOS, classes in the object-oriented paradigm can be treated as sorts, inheritance hierarchy as sort hierarchy, instance creation as assertion of state predicates, an instance name as a constant whose sort

corresponds to the class of the instance, and message sending as subgoal proving. In spite of these salient features for supporting object-oriented programming, EPOS has some problems. To overcome these problems we have designed an object-oriented many-sorted logic language TRY. A T R Y program is translated into an extended EPOS program which contains some features that EPOS does not support. These new features may be supported by extending the unification algorithm and control mechanism of EPOS; but this approach cannot derive as much advantages as desired because a large complete and minimal set of unifiers can make the control mechanism of Prolog complex and the use of expressive sort symbols also makes unification complex. Thus, we decided to translate an extended EPOS program into an EPOS

Vol 35 No 4 April 1993

1 Schaffert, C, Cooper, T, Bullis, B and Wiipoit, C 'An introduction to Trellis/Owl' Proc. OOPSLA (1986) pp 9-16 2 Moon, D A 'Object-oriented programming with flavors' Proc. OOPSLA (1986) pp 1-8 3 Moon, D A 'The common lisp object-oriented programming language standard' in Kim, W and Lochovsky, F H (eds) Object-oriented concepts, databases, and applications ACM Press (1989) pp 49-78 4 Bobrow, D G 'Common loops: merging lisp and objectoriented programming' Proc. OOPSLA (1986) pp. 17-29 5 Zaniolo, C 'Object-oriented programming in Prolog' Proc. Int. Syrup. Logic Programming (1984) pp 265-270 6 Gallaire, H 'Merging objects and logic programming: relational semantics' Proc. AAAI (1986) pp. 754-758 7 Fukunaga, K 'An experience with a Prolog-based objectoriented language' Proc. OOPSLA (1986) pp 224-231 8 Kahn, K et al. 'Objects in concurrent logic programming language' Proc. OOPSLA (1986) pp 242-257 9 Leonardi, L and Mello, P 'Combining logic- and objectoriented programming language paradigms' Proc. 21st Hawaii Int. Conf. Systems Science (1988) pp 376-385 10 Brachman, R J and Schmolze, J G 'An overview of the KL-ONE knowledge representation system' Cognitive Science Vol 9 No 2 (1985) pp 171-216 11 Cohn, A G 'A more expressive formulation of many sorted logic' J. Automated Reasoning Vol 3 No 2 (1987) pp 113-200 12 Irani, K B and Shin, D G 'A many-sorted resolution based on an extension of a first-order language' Proc. IJCAI (1985) pp 1175-1177 13 Walther, C 'A many-sorted calculus based on resolution and paramodulation' Proc. IJCAI (1983) pp 881-891 14 Walther, C 'Many-sorted unification' J. ACM Vol 35 No 1 (1988) pp 1-17 15 Cohn, A G 'On the solution of Schubert's steamroller in many-sorted logic' Proc. IJCAI (1985)pp 1169-1174 16 Walther, C A many-sorted calculus based on resolution and paramodulation Pitman and Morgan Kaufmann (1987) 17 Ait-Kaci, H and Nasr, R 'Login: a logic programming language with built-in inheritance' J Logic Prog. Vol 3 (1986), pp 185-215 18 Enders, R The object-oriented extension of Prolog-XT Technical Report, INF2-ASE-7-89, Siemens AG. 19 Huber, M and Varsek, I 'Extended Prolog for order-sorted resolution' Proc. 1987 Symp. Logic Programming (1987) pp 34-41 20 Shapiro, E Y 'A subset of concurrent Prolog and its interpreter ICOT Technical Report ICOT n.3, (1983)

253