TelecomParis_IPParis.png Telecom Paris
Dep. Informatique & Réseaux

nils.png Nils HolzenbergerHome page

March 2024

5

NeurSymAI.png Neuro-Symbolic Artificial Intelligence

with             Simon Coumes     portrait.jpg         and         Zacchary Sadeddine     Zac.jpg

            other AI courses


5

Summary










Always useful: SWI-Prolog documentation (mainly 4th section)

Problem solving with Prolog

From the start, artificial intelligence focussed on problem solving, certainly because it is the part of intelligence human beings are mainly aware of. Problem solving is an issue of major importance in many domains: games, planification, diagnosis, decision, argumentation, robotics, help systems... Artificial intelligence got its first success in the field of problem resolution, especially with "expert systems".

The monkey, the box and the banana

banane.pngsinge.gif The monkey must find a way to reach the banana which cannot be taken from the ground. She has a few actions at her disposal:

Her problem consists in performing these actions in the right order and at the right place in the room.

The following program is adapted from I. Bratko (Prolog, Programming for Artificial Intelligence, 2nd ed. 1990). It involves two predicates, action and success. The action predicate has three arguments: the initial state, the performed action, and the final state:


action(InitialState, Action, ObtainedState)

Each state is represented by a functor, the state functor, which has four arguments:

For instance: state(middle, onbox, middle, not_holding)


% Definition of the possible actions with the state associated constraints
action(state(middle, onbox, middle, not_holding),
        grab,
        state(middle, onbox, middle,h olding)).
action(state(P, floor, P, T),
        climb,
        state(P, onbox, P, T)).
action(state(P1, floor, P1, T),
        push(P1, P2),
        state(P2, floor, P2, T)).
action(state(P1, floor, B, T),
        walk(P1, P2),
        state(P2, floor, B, T)).

Notice that giving the same name to two variables inside a same clause is meaningful: it imposes that the two variables are linked and have the same value. For instance, the climbing action action(state(P, floor, P, T), climb, ...) is possible only if the monkey and the box are located at the same place. However, the scope of a variable being limited to the clause, two variables having the same name but in two distinct clauses are not linked.

Another important remark: state is a functor; a functor seems similar to a predicate, but it is the argument of a predicate or of another functor; some functors (especially the arithmetic functors such as +(3,2)) can be evaluated (try: ?- is(X,+(3,2)).).


% Definition of the success conditions in the problem of the monkey
success(state(_, _, _, holding)).
success(State1) :-
    action(State1, A, State2),
    write('Action : '), write(A), nl, write(' --> '), write(State2), nl,
    success(State2).

(during unification, the sign "_" is a joker that can match anything; the nl predicate prints a ‘new line’ character).

You may retrieve the program from ➜ there.

Ask the interpreter:

?- success(state(door, floor, window, not_holding)).
Action : walk(door, _G582)
--> state(_G582, floor, window, not_holding)
Action : climb
--> state(window, onbox, window, not_holding)
Action : push(window, _G590)
--> state(_G590, floor, _G590, not_holding)
Action : climb
--> state(_G590, onbox, _G590, not_holding)
Action : grab
--> state(middle, onbox, middle, holding)

The interpreter is able to search for actions that will lead it to success (notice the variable names invented by the interpreter, such as _G582). The behaviour of the monkey can be described as follows: it walks to the place where it can climb on the box. It finds itself on the box near the window, which leads to failure. It changes its mind and pushes the box from a place where it can be pushed (window) to another place. At the (not yet instantiated) new place, the monkey will climb on the box and grab the banana. This last place is eventually instantiated as being middle.

Notice that the main part of the search is performed by the interpreter, and not by the developer who "only" entered possible actions and success conditions.

Monkey (1)
Change the order of actions, for instance by putting the walk action first. What do you observe?

    

Monkey (2)
Instead of printing the monkey’s actions, we wish to store them into a list. You may use an additional argument Plan in the success predicate. Store actions into Plan once they have contributed to a successful state. Copy the clauses of the success predicate below (and those clauses only).

    

300px-Tower_of_Hanoi.jpeg

The Tower of Hanoi (optional)

Look at the various ways to solve the famous Tower of Hanoi problem with Prolog.

Accumulation

Central recursion is a fundamental phenomemon, not only in Natural language processing (as we will see in another chapter), but more generally each time the set of states visited by an algorithm make up a tree that may grow by any of its branches.

A recursive algorithm goes through three phases: descent, stop at bottom, ascent. Prolog programming takes advantage of these three phases. The following program illustrates the point. Its job is to reverse a list to buid up its mirror list.


% bad solution (double recursion):
mirror([ ], [ ]).
mirror([X|L1], L2) :-
    mirror(L1,L3),
    append(L3, [X], L2).     % append will dig into the list a second time

This solution isn’t very clever, since to put X at the end of the list, append must go through the whole list anew. The following solution is more elegant. It makes use of the concept of accumulator. The accumulator (second argument in invert) is a list that gets filled during descent into recursion. Warning: recursion is amnesic when it returns up. In order not to loose the accumulator’s content, one has to save it. The third clause saves the accumulator into the third argument of invert. This argument is then dutifully copied during ascent, after each recursive call terminates (variable L3).


% better solution with accumulator:
mirror2(Left, Right) :-
    invert(Left, [ ], Right).
invert([X|L1], L2, L3) :-    % the list is 'poured'
    invert(L1, [X|L2], L3).    % into the second argument
invert([ ], L, L).        % at the deepest level, the result L is merely copied

The next exercise aims at checking whether a list is a palindrome. In French, "ressasser" and (ignoring spaces) "Esope reste ici et se repose" or "Engagez le jeu, que je le gagne!" are palindromes. In English, "rotator", "Too bad I hid a boot" or "No devil lived on" are palindromes. One of the most famous palindromes (and probably the longest one, as it has 1355 words!) has ben written by George Perec. If you know of a funny palindrome, don’t hesitate to share it.

Palindrome
Use mirror2 to write palindrome that checks whether a list is a palindrome.

Then, think of a second version of palindrome using an accumulator. The point is to ‘pour’ the beginning of the list to check into the accumulator, and to sopt when the end of the list is equal to the accumulator’s content. With this solution, one goes through only half of the list. The remainder of the work is achieved by Prolog’s unification algorithm.

    


You may retrieve a list of words of your favourite language from the Web, and then try to generate palindromes à la Perec. To do so, you’ll need to have a look at SWI-Prolog’s documentation (file reading, word to char list conversion, ...). Then, you’ll need to write a program that would judge the aesthetics of the generated palindrome. Well..., not that easy!

Knowledge representation


Using Prolog’s memory

’assert’ and ‘retract’

Prolog offers several means to store knowledge. The most obvious one is to store knowledge in a file 'MyKnowledgeBase.pl' that is then executed using the interpreter (or by executing the instruction consult('MyKnowledgeBase.pl'). from another program). But Prolog offers another standard way to manage memory. We study it now (in addition, interpreters offer various sophisticated means to manage large knowledge bases; we won’t consider them here).

Standard basic predicates to deal with memory are assert and retract. The former stores a clause in memory, as if it would be part of the program (so you can modify programs ‘on the fly'). The latter, retract, achives the converse operation. Let’s observe how these predicates do the job with an example adapted from I. Bratko (1990. PROLOG - Programming for Artificial Intelligence. Addison-Wesley) :


:- dynamic(sunshine/0). % necessary with SWI-Prolog.
:- dynamic(raining/0). % necessary with SWI-Prolog.
:- dynamic(fog/0). % necessary with SWI-Prolog.

nice :-
    sunshine, not(raining).

funny :-
    sunshine, raining.
disgusting :-
    raining,fog.
raining.
fog.

When executing a ‘directive’ like    :- dynamic(pred/a)., SWI-Prolog knows that the predicate pred which has arity a (arity = number of arguments) can be modified dynamically (predicates are otherwise ‘compiled’ by SWI-Prolog and they can no longer be altered on the fly). Let’s execute our program:


?- nice.
    no.
?- disgusting.
    yes.
?- retract(fog).
    yes.
?- disgusting.
    no.
?- assert(sunshine).
    yes.
?- funny.
    yes.

One may dynamically add clauses that are not mere facts.


?- assert((wet :- raining, not(umbrella))). % note the parentheses
    yes.
?- wet.
    yes.
?- assert(umbrella).
    yes.
?- wet.
    no.

You may use Prolog’s memory to print them:


myprint :-
    retract(item(X)), % reussit tant qu'il y a des items
    write(X),nl,
    fail.
myprint.

This version erases items from memory. If this is problematic, the following version can be used:


myprint1 :-
    retract(item(X)),
    !, % avoids unwanted behahaviour if some predicate fails after a call to myprint1
    myprint1,
    write(X),nl,
    asserta(item(X)). % asserta = version of assert that adds item on top of the memory stack
myprint1.

Take one minute to think about the way this predicate works: myprint1 thoroughly empties memory by erasing items during the recursive descent, then retract fails (as there are no items left in memory), and this gives control to the second defining clause of myprint1; then the     program climbs back from the bottom of recursion, writing and restoring items.

Note that there are two additional standard versions of assert to control where the memorized item is placed in memory: asserta places the item on top of the stack and assertz at the bottom. SWI-Prolog considers assert and assertz as synonymous.


?- assert(a(1)).
true.
?- assert(a(2)).
true.
4 ?- a(X).
X = 1 ;
X = 2.

?- asserta(b(1)).
true.
?- asserta(b(2)).
true.
?- b(X).
X = 2 ;
X = 1.

Caveat: Prolog’s memory, unlike clause execution, is global: it is seen from everywhere and is not destroyed during backtracking.


?- assert(well_known(katy)), fail.
    False.
?- well_known(X).
    X = katy.

The predicate retractall erases all matching items from memory. It always succeeds (even when there is no such item).


?- assert(well_known(katy)), retractall(well_known(_)).
    true.
?- well_known(X).
    false.

Empty
Use retract to write a predicate empty that behaves like retractall: it should erase all memorized facts about the predicate given as argument. Note that empty should always succeed.
Then try:

    assert(well_known(katy)).
    assert(well_known('Elvis')).
    assert(well_known(madonna)).
    assert(well_known(michael)).
    empty(well_known(_)).
    
    ?- well_known(X).
    false.

    


The ‘findall’ predicate

findall(X, pred(X), L) executes a predicate pred given as its second argument. All values of X that make pred suceed are stored in L. This is quite convenient when one wants to query a knowledge base.


?- findall(P, parent(P,_), ParentList).
    ParentList = [marge, marge, marge, homer, homer, homer, abraham, abraham, mona|...].

The variable may be decorated:


?- findall(p(P), parent(P,_), ParentList).
    ParentList = [p(marge), p(marge), p(marge), p(homer), p(homer), p(homer), p(abraham), p(abraham), p(...)|...].

We may use Prolog’s memory (with assert and retract) to write a predicate findany that mimics findall.
This predicate will be called the same way:

findany(Var, Pred, Results).

By executing Pred in the first place, the link (that is supposed to exist) betweeen Var and Pred gets instantiated.
The instantiated value of Var can be stored using assert; for instance: assert(found(Var)). Then, one can force backtracking by inserting fail.
Eventually, when Pred fails for good, it’s time to recover all memorized values and to put them into a list.

    

Findany
Write findany that mimics findall.


    findany(Var, Pred, Results).

In a first clause, call Pred, then assert found(Var) and use fail to force backtracking. When Pred eventually fails, another predicate collect_found should gather results into a list.

    

Semantic networks

Semantic networks rely on a simple idea: base knowledge representation on concepts rather than on logical relations. In a semantic network, concepts are nodes in a graph and predicative relations are the edges. The following example, written in Prolog, can easily be drawn as graph. The isa relation means "is a".

Birds.png
% adapted from I. Bratko - "Prolog - Programming for Artificial Intelligence"
% Addison Wesley 1990
isa(bird, animal).
isa(albert, albatross).
isa(albatross, bird).
isa(kiwi, bird).
isa(willy, kiwi).
isa(crow, bird).

food(albatross,fish).
food(bird,grain).

locomotion(bird, fly).
locomotion(kiwi, walk). % kiwis don't fly, it seems

Semantic networks are interesting in several respects. In their graphic form, they are easier to read than rules; they can be used to perform association (by propagating influences); The isa relation can be used to define inheritance.


locomotion(X, Loc) :- % inheritance rule
    isa(X, SuperX),
    locomotion(SuperX, Loc).

This way of writing inheritance rules is not really smart. One needs a different inheritance rule for each relation! Thanks to Prolog, one can write a more general inheritance mechanism.


known(Fact) :-
    Fact, % checks wether Prolog succeeds while executing Fact
    !. % no need to seek further
known(Fact) :-
    Fact =.. [Property, Concept, Value], % Fact is a foncteur, with the concept as first argument.
    isa(Concept, ParentConcept), % getting the parent concept
    SuperFact =.. [Property, ParentConcept, Value], % substituting for the parent concept
    known(SuperFact). % This will instantiate Value

We are using one of Prolog’s great syntactic features: the "=.." operator. This tool transforms functors into lists (or the converse). Very convenient to maipulate functors and predicates.


?- f(a,b) =.. [f, a, b].
true.    

The above program is available from ➜ there.

Semantic Network
Try the solution based on predicate known with the following exemple:


?- known(locomotion(albert, L)).

What about the kiwi’s locomotion?

    

Note that the semantic network works appropriately only if it is "read" with an instatiated object and an uninstantiated value. In other words, never ask something like known(locomotion(kiwi,fly)). To check a fact with the program as it stands, you have to use an intermediate variable:


?- known(locomotion(crow, M)), M = fly.
M = fly.

?- known(locomotion(kiwi, M)), M = fly.
false.

(It would be possible to prevent such inappropriate use with a test like var(Value).)

Non-monotonic reasoning consists in the fact that the set of inferred facts does not necessarily increase when knowledge is augmented. In other words, knowing more may lead to inferring less.

Monotonic reasoning
Write a predicate habitat(Animal, Location) to express the fact that non-flying animals live on the continent.
The predicate may specify an unknown location by default.
Since ostriches are birds, the question:    known(habitat(ostrich, L)). should answer L = unknown.

Add the piece of knowledge:    asserta(locomotion(ostrich, run)).
and verify that habitat(ostrich, L). now answers L = continent.

    

Ontologies

Ontologies are conceptual hierarchies, supposed to store concepts as an ordered set that uses inheritance and produce inferences. Our previous examples of semantic network are examples of ontologies.
Ontologies have always been a classic tool of artificial intelligence. They recently experienced a renewed interest in a much larger community concerned with the "Semantic Web".

Some professional sectors are involved in the definition of ontologies of significant sizes (several thousand concepts). Visit for example Mikrokosmos, CYC, Wordnet, ConceptNet, DOLCE (general ontologies for natural language processing), Menelas (medical reports in coronary angiography), SNOMED-CT (medical ontology, 3.105 concepts), CAB (law), Dublin Core ontology (bibliography). You may like to compare the top concepts of ontologies like Mikrokosmos, DOLCE, ConceptNet and CYC.

The construction of ontologies is often achieved by human operators (which presupposes considerable investments). Some tools exist to facilitate the task. One of the best known in the world of research is% L + http: //protege.stanford.edu/ (Protégé), developed at Stanford University. We may also mention DOE (Differential Ontology Editor), OntoLingua (also at Stanford), HOZO (Osaka University).

One of the primary objectives of ontology development is to facilitate disambiguation, to make inferences, and ultimately to allow the development of search engines based on meaning (and not just on words). See for example the engine CORESE(developed at INRIA). It is therefore essential that the structure associated with a concept be easily accessible, if possible in a standardized mode. The W3C(www consortium) proposes standards based on markup languages (built on XML), such as RDF or OWL(Web Ontology Language).

If all the semantic resources were described according to the same ontology, developing intelligent search engines would be relatively easy. However, such global standardization is impossible because of the variety of subject areas and the arbitrary nature of certain choices, and is unlikely to be desirable for many other reasons. We must therefore imagine systems that are able to align ontologies automatically. The task is however not easy.

The main hope, both for standardization and for matching ontologies, but also for their use in reasoning, lies in the use of logic, and in particular in the development of description logics.

Description logics

Description logics have been imagined to represent knowledge in a form that can be exploited for reasoning, so that requests such as "Does a kangaroo have lungs? Can a kangaroo be drowned?" might be answered, despite the fact that the information is not explicitly included in the data provided to the system. Description logics realize a compromise between the power of expression (they allow the use of variables and quantification) and the feasibility of computations (whether a logical expression is satisfiable) in reasonable time. They are restrictions on the logic of predicates (which will be the subject of a topic of this course).

The syntax of description logic is compact and leaves some variables implicit:

Mother = Woman ⊓ hasChild.Person

(⊓ designates conjunction) translastes into logic as:


Mother(x) ≡ Woman(x) ∧ (∃y) (hasChild(x, y) ∧ Person(y))

More generally, here is the translation into predicate logic of expressions involving quantifiers:

∃r.C = (∃y) (r(x, y) ∧ C(y))
∀r.C = (∀y) (r(x, y) ⊃ C(y))

A family ontology:

woman ≐ person ⊓ female
man ≐ person ⊓ ¬ female
mother ≐ woman ⊓ ∃ child.person
father ≐ man ⊓ ∃ child.person
parent ≐ person ⊓ ∃ child.person or: parent ≐ mother ⊔ father
grandmother ≐ mother ⊓ ∃ child.parent
motherWithoutDaughter ≐ mother ⊓ ∀ child.¬female
spouse ≐ woman ⊓ ∃ married_to.man
monogamousSpouse ≐ woman ⊓ ∃ married_to.man ⊓ (< married_to 1)

(⊔ designates disjunction and ¬ designates negation).

A knowledge base in description logic includes:

The above example is a T-Box. A corresponding A-box might be:


daughterlesswoman(Paulette)
child(Paulette, Pierre)
child(Paulette, Jacques)
father(Pierre)
child(Pierre, Marinette)

It is easy to see that a knowledge base might be inconsistent. The strength of description logics is to be able to demonstrate the coherence (and therefore the satisfiability) of a given knowledge base.

Description logics (as a matter of fact, there are several) differ by the logical connectors they allow. The AL.gif language Includes negation of atomic concepts, conjunction, universal quantifier ∀, and a restriction of the existential quantifier ∃ such as: ∃ child.truc.gif (truc.gif designates tautology, so ∃ child.truc.gif means that the individual has a child, but is it not possible to add any further restriction on the existing child). The AL.gif language can be augmented to include full existential quantification, union, predication on cardinality, negation of complex concepts, hierarchy of relations (sort of second order predication), enumeration of possible values, and do on. Conversely, it is possible to remove negation and existential quantification. For example, the ontologies editor Protégé supports the negation of complex concepts, the hierarchy of relations, enumerations and cardinality.

The simplest description logics, such as AL.gif without negation and existential quantification, have the advantage of offering satisfiability test that is decidable in polynomial time. Decidability becomes exponential for more complex formalisms. For a first-order logical formalism, there is only semi-decidability (one is assured to prove satisfiability in a finite time if the formula is satisfiable, but one can loop for ever if the formula is not satisfiable).

Description Logic
Based on the examples above, define the concept of aunt (let’s assume that the sister relationship is available).
(you may replace symbols with appropriate words such as ‘exist’ and ‘and-square').

    

Note, with regard to this exercise, that atomic predicates and relations are the building blocks of a language like AL.gif. It is therefore not possible to deduce the sister relationship from the child relationship, as would be done in Prolog. Description logics have a certain power of expression which is just sufficient to represent terminological knowledge, and their limitations are necessary to make effective reasoning possible. They don’t, however, have the description and inference power of the predicate logic.

Reading suggestions:

Baader, F. & Nutt, W. (2003). Basic description logic. In F. Baader, D. L. McGuinness, D. Nardi & P. F. Patel-Schneider (Eds.), The description logic handbook: Theory, implementation, and applications, 47-100. Cambridge University Press.

            
Line.jpg

Back to the main page