Hack Jam Log Book is a log of progress made in and around a weekly hack session. Topics include natural language processing, high energy electronics, linguistics, interface design, &c. Enjoy.

Recent Posts:

Archives:

22.10.08

 

NLP: Grammar Trees to Logical Statements

I'm going to start a series of detailed posts about the comprehension module. This is the section that translates a grammar tree into a logical statement. For this discussion, we'll be looking at a simplified version of my simplified version of English grammar. We'll expand our grammar in future posts. Since I've started this post, I've improved my approach in this area as well, so you'll be seeing the evolution of this code, with a couple weeks lag time.

It also gives me an opportunity to introduce a bit of Haskell. I'll introduce you to Haskell just enough to understand what I'm doing. If you want to learn it well enough to use it, I suggest one of these fine tutorials.

> module HackjamNLP where

This post is written in literate Haskell. The lines begining with ">" are source lines, everything else is a comment. You can copy this post to a file and load it into an interpreter if you like.

> data Sentence = Declarative NounPhrase VerbPhrase
>
> data NounPhrase = ANoun Word
> | APronoun Word
> | Name Word
>
> data VerbPhrase = AVerb Word

What I'm doing here is defining three new types, Sentence, NounPhrase, and VerbPhrase, each with one or more type constructors. So a Sentence can be constructed with Declarative, a NounPhrase with ANoun, AProunoun, or Name, and VerbPhrase with Verb. Everything after the type constructor's name are the types each constructor requires to build a value of that type. In other code, here's a rough equivalent to Sentence's Declarative constructor in a bastard Java-like:

: Sentence Declarative(NounPhrase np, VerbPhrase vp) { ... }

So type constructors are like functions that return values of a given type (but more useful, as we'll see later).

> data Word = Word {
> wordString :: String,
> partOfSpeech :: PartOfSpeech,
> isPlural :: Bool
> }

Here we see another syntax for declaring a data type. It is common to name the constructor for a type the same thing as the type itself when there is only one constructor for that type. The :: can be read as "has type", so we can reason that a Word is made of wordString of type String, a partOfSpeech of type PartOfSpeech, and isPlural of type Bool. Each of these identifiers is a function that can be applied to a Word to get it's corresponding field.

You've probably noticed that Haskell is case sensitive. Actually, the upper/lower case convention I'm using isn't convention at all; It's required by syntax. All types and type constructors (and names of modules, but I'm not going there) are required to be uppercase, everything else is must be lowercase.

> data PartOfSpeech = Noun | Verb | Adjective | Article | Pronoun
> | Adverb | Unknown

One last definition. Here I'm enumerating the types of speech that I'm using. This is the same syntax as before, except none of these have any parameters, and I compacted the formatting.

Now I can build Sentences out of Strings, PartOfSpeeches, and Bools. As a quick example, let's quickly build a Sentence representing "I win.":

> iWin = Declarative (APronoun (Word "I" Pronoun False))
> (AVerb (Word "win" Verb False))

Tada.

Again, we're going to take for granted that some other nice module has generated these grammatical trees for us. We should only be concerned with converting them to logical statements. First, we define a representation of logical statements. This representation won't describe all logical statements; I've left out constructors that I won't be using here to keep things simple.

> data LogicSentence = Atom ID [Term]
> | And LogicSentence LogicSentence
> | Implies LogicSentence LogicSentence
> | ForAll Term LogicSentence
> | Exists Term LogicSentence
> deriving Show
>
> data Term = Variable ID
> | Set [Term]
> deriving Show
>
> type ID = String

The [] brackets in [Term] indicate a list of that type, and the last line defines ID to be a type equivilant to a String.

The deriving statements for Term and LogicSentence tell the compiler to generate a default implementation of a class. In this case, we want these types to be instances of the Show class so we can convert them to strings and display them on our terminals. This default necessarily be pretty, as we'll see later. We could also have it derive other classes like Read (to convert strings to the type), Eq (equality), and Ord (ordering, i.e. less than, greater than). Think of derive as saying "You're so smart, Mr Compiler, I'm sure you can figure out this on your own."

Now we can start building LogicSentences.

> x = Variable "x"
> iWinLogic = Exists x ((Atom "speaker" [x]) `And` (Atom "win" [x]))

Here I've put And inside backticks to change it from a prefix operator (like "f" in "f(x,y)") to an infix operator (like "+" in "x + y"). The braces are back, and again they denote lists. [x] creates the list with x as it's only element.

We've arrived at the point where we can work on what we came here to do. We'll tackle a bit at a time, starting with converting just the noun phrase to a logical sentence.

> convertNounPhrase :: NounPhrase -> LogicSentence

Here I've declared the type of something I'm calling convertNounPhrase. All this says is that it's a function that takes a NounPhrase and returns a list of LogicSentece. The compiler is smart enough that it could infer the type of the function on it's own, but it's common practice to specify it explicitly. There are two reasons for this. First, it serves to improve readability and provides documentation for the author. Second, it helps to locate compile errors by making sure the compiler arrived at the same type the author intended

> convertNounPhrase (Name name)
> = Exists x (Atom ("called-" ++ wordString name) [x])

Haskell is nice and lets us define functions in parts. Here we define the convertNounPhrase function when given a NounPhrase built with the Name constructor. This is called pattern matching, and it's wonderful for building functions like this cleanly. Haskell will try each definition of convertNounPhrase in the order defined until a match is found (if none are found, it throws an exception). Note that name here doesn't refer to the NounPhrase built with Name, but the word used to build Name with.

A name, by itself, indicates that there is something that is called by that name. In other words, our representation of "Adam" is: there exists some x such that called-Adam(x) is True. (++ is the concatenation operator, and strings are just lists of Chars, so that ("called-" ++ wordString n) buisness builds strings like "called-Adam".)

> convertNounPhrase (ANoun n)
> | isPlural n = ForAll x (Atom (wordString n) [x])

Besides specifying the manner in which a parameter is constructed, we can also place /guards/ in our pattern matches. This definition only matches Nouns built with a Word that satisfy isPlural. For the moment, we'll assume that no non-plural nouns without articles (the, a, an) are passed by the grammar tree builder.

The case statement draws near!

> convertNounPhrase (APronoun n)
> = case wordString n of
> "I" -> Exists x (Atom "speaker" [x])
> "you" -> Exists x (Atom "audience" [x])
> otherwise -> Exists x (Atom "in-context" [x])

I won't go into the syntax of case; I'm sure you can figure out how it works.

Note I'm leaving out a number of possibile pronouns here in the name of brevity.

> convertVerbPhrase :: VerbPhrase -> (Term -> LogicSentence)

We're getting trickier here. convertVerbPhrase is a function that takes a VerbPhrase and returns a list of functions. These functions each take a Term and return a LogicSentence. In Haskell, all functions are curried, so I could remove the parentheses from this type definition if I wanted to. I'm leaving them in for readability.

Why do we want to return a function here? A verb phrase describes an action or relation. It needs the subject of the sentence to complete it's meaning. If I say "dances a jig.", it's not a complete sentence; there is an immediate question of "Who?". It needs the who for the full meaning.

> convertVerbPhrase (AVerb v) = (\subject -> Atom (wordString v) [subject])

We'll expand verb phrases soon, but for now, we'll just deal with a single verb. This definition shows the syntax for a lambda function: (\x -> ... ). When we apply a term to the result of convertVerbPhrase, that term will be used in place of subject.

> convertSentence :: Sentence -> LogicSentence
> convertSentence (Declarative np vp)
> = let nounSentence = convertNounPhrase np
> subject = subjectOf nounSentence
> action = convertVerbPhrase vp
> in combineNVSents nounSentence (action subject)

Finally, the goal of the post. This demonstrates a let block. Those equal signs don't mean what they do in imperative programming. That is to say, we aren't evaluating convertNounPhrase np and storing the result as nounSentence, we are declaring that nounSentence is equivalent to convertNounPhrase np. We could have wrote this function as

> convertSentence2 (Declarative np vp)
> = combineNVSents (convertNounPhrase np)
> (convertVerbPhrase vp
> (subjectOf (convertNounPhrase np)))

So now we need to define subjectOf and combineNVSents, and we'll be done for now.

> subjectOf :: LogicSentence -> Term
> subjectOf (ForAll t _) = t
> subjectOf (Exists t _) = t

Another feature of Haskell's pattern matching: we can tell the compiler that we don't care about some terms. "_" is a wildcard. It will match anything for that term.

Note that we don't have to define subjectOf for all possible Sentences. We'll accept a Exception if it's called for a Sentence it's not defined for. We're careful above to have convertNounPhrase only return these two types of sentences, precisely so this funtion will work.

> combineNVSents :: LogicSentence -> LogicSentence -> LogicSentence
> combineNVSents (ForAll t npDescription) vpDescription
> = ForAll t (npDescription `Implies` vpDescription)
> combineNVSents (Exists t npDescription) vpDescription
> = Exists t (npDescription `And` vpDescription)

Nothing new here.

Now we can load this post into a Haskell interpreter (I'm using ghci) and try it out:

ghci> convertSentence iWin
Exists (Variable "x") (And (Atom "speaker" [Variable "x"]) (Atom "win" [Variable "x"]))

I win.

Comments:
Fun post... I've always been hoping we could put together a little NLP Haskell community. I think I can name 4 people who might be able to contribute something to it. And maybe we can find some way to work with the Haskell bioinformatics people.
 
Post a Comment

Subscribe to Post Comments [Atom]





<< Home

This page is powered by Blogger. Isn't yours?

Subscribe to Posts [Atom]