Prolog Weeks 3-4: Natural Language to Predicate Calculus

How to do it

Parsing

Most of what you need is provided in chapter 9 of the textbook, in which the authors skillfully motivate the parsing techniques of Prolog. You should read the whole chapter carefully and understand why and how parsing is done the way it's done. Nonetheless, I'll adumbrate the end-product in a nutshell.

The parsing in Prolog is done by treating a sentence as a list of strings, and then trying to match partitions of the list to the grammatical rules we provide. (The DCG notation '-->' is simply a way to make the list processing more convenient.) This means you have to turn a raw sentence into a list of atoms if you want a pleasant interection with the system. Since this is not the focus of the exercise, you can find the code that does the job here. With this code, the sentence "Boys like girls!" supplies the list [boys,like,girls].

To make the idea concrete, apply the code on p. 221 to "The man sings", or [the,man,sings]. The initial call has the confusing form sentence([the,man,sings],[]). You're asking the question "Is this a legal sentence?" in this way because the second argument is an empty list [] if and only if the sentence is parsed correctly. To see this, trace the code. By the first rule, you'll have noun_phrase([the,man,sings],[]) (you won't consider the verb_phrase part yet because Prolog employs depth-first search in execution). By the second rule, you'll have determiner([the,man,sings],S1), where the fifth rule 'swallows' the word the and leaves the remaining segment [man,sings] to S1, and subsequently we get noun([man,sings],S). The sixth rule 'swallows' the word man and leaves the remaining segment [sings] to S. Now that the noun_phrase part is done, we backtrack to the first rule, and since the S = [sings] in the second rule is precisely S1 in the first rule, we call verb_phrase([sings],S). By the third rule, we call verb([sings],S), where by the last rule S is unified with []. Since this is what we originally asked (sentence([the,man,sings],[])), we obtain the answer true.

What the DCG notation does is it hides the two arguments that function as 'workbench' lists. So the rule sentence(S0,S) :- noun_phrase(S0,S1), verb_phrase(S1,S) is equivalent to the rule sentence --> noun_phrase, verb_phrase. Then how do I provide the input, you may ask. Simple; since those two are exactly the same, you must treat it exactly the same. Thus, when you ask, you'll still have to supply the argument lists in the same way, sentence(L,[]), where L is a list of atoms.

To recover the parse tree, you have to do a bit more. When you ask a question, you must provide a placeholder for the tree. So the question now looks like sentence(T,L,[]), where T would be unified with the parse tree of L eventually. This unification can be done in the rule for sentence,

sentence(sentence(NP, VP)) -->
	noun_phrase(NP), verb_phrase(VP), sentence_finisher.
(I'm getting rid of the period, the bang, the question mark by using sentence_finisher.) Notice that the two latter arguments, L and [], are being handled behind the scene, but we must dictate any arguments before them. And we're dictating it in such a way that the T in the original call will be unified with the form sentence(NP, VP), where NP and VP will be unified with the tree for a noun phrase and the tree for a verb phrase via similar rules.

In addition, you can always add a new variable to keep a feature of the grammar, such as number agreement. For instance, my noun rule is defined as

noun(X,Y,noun(N)) --> [N], {is_noun(X,Y,N)}.
where the first argument X contains the information about number agreement, the second argument Y contains the information about whether the noun starts with a vowel sound (so that I can use 'an' instead of 'a' in the case of indefinites), the third argument is dictating how the parse tree (which will be sent upward) is scribed. An instance of such a noun is is_noun(singular,vow,apple).

Using this as a springboard, you can develop any grammar you want in your parser. Make sure you consult the textbook for the complete picture of parsing.

Translating

We'll see how translation is done with an example. Let's consider the sentence All big apples are delicious. After parsing, we have the parse tree
T = sentence(noun_phrase(determiner(all), adjective(big), noun(apple)),
		     verb_phrase(be(is), adjective(delicious)))
Now, look closely at the noun phrase:
noun_phrase(determiner(all), adjective(big), noun(apple))
In order to turn it into a logical expression, we must know what exactly it's referring to. This is referring to any apple that is big - the intersection between the qualifier apple and the qualifier big. So, we can interpret this as:
all(x, apple(x)&big(x)),
where all is the universal quantifier and & is the AND operator. (In Prolog, you can introduce this new operator by saying op(500,xfy,&).) This is done in my code with
np(Var,noun_phrase(DET,ADJ,N),P3) :-
	det(Var,DET,P1,P2,P3),
	adj(Var,ADJ,P1),
	n(Var,N,P2).
where Var is the variable (i.e., x), P3 is the final interpretation (i.e., all(x, apple(x)&big(x))), and P1 and P2 are the intermediate interpretations. That is, the determiner 'all' is dealt with the rule
det(Var,determiner(a),P1,P2,all(Var, (P2 & P1)))..
Do you see what this is doing? In the np rule above, it's pulling in the interpretations for the adjective and the noun, which are done with
adj(Var,DESC,P) :-
	DESC =.. [adjective,ADJ],
	P =.. [ADJ,Var].
and
n(Var,DESC,P) :-
	DESC =.. [noun,N],
	P =.. [N,Var].
(The operator =.. is very useful when you need to manipulate functional notations. Refer to the textbook.) Combining all, the original np rule is 'filled up' to the followng:
np(x,noun_phrase(determiner(a),big(x),apple(x)),P3) :-
	det(x,determiner(a),big(x),apple(x),P3),
	adj(x,big,big(x)),
	n(x,apple,apple(x)).
where P3, according to the det rule above, is unified with the final expression: P3 = all(x, (apple(x) & big(x))).

Next, look closely at the verb phrase

verb_phrase(be(is), adjective(delicious)).
Likewise, to turn this into a logical form, we need to first decide what it means. This is saying that if x is the subject of this verb phrase, then x is delicious. It can be simply formulated by the following rule:
vp(Var,all(A,B),verb_phrase(BE,ADJ), all(A,B => C)) :-
	BE =.. [be,is],
	adj(Var,ADJ,C).
Similarly, you can introduce the new implication operator by saying op(600,xfy,=>). Note the conditions for the arguments. I'm requiring the subject to be of the form all(A,B), because the subject of other form has a different interpretation (e.g., exists(A,B)). I'm also requiring (obviously) the verb phrase consist of a BE verb (other BE verbs like 'are' are already conditioned to 'is' in the parsing phrase in my parser) and an adjective. Finally, note that I'm repeating the expression for the universal quantifier 'all' because I'm including C, the claim about the subject, into the scope of the quantifier. Thus, the the output will be
all(x, (apple(x) & big(x)) => delicious(x)).
Therefore, the whole sentence can be put together with the rule
s(sentence(NP,VP),F) :-
	gensym(x,X),
	np(X,NP,T), vp(X,T,VP,F).
The function gensym(x,X) provides you with an unused notation for a variable (e.g., x1, x2, ...).

Using this as a springboard, you can develop any logical interpretation you want in your translator. Make sure you try to make the interpretation as accurate as possible.