CHAPTER 8    Visual Prolog's fact sections

 

In this chapter, we describe how you declare facts sections and how you can modify the contents of your fact section.

A facts-section is composed of facts that you can add directly into and remove from your Visual Prolog program at run time. You declare the predicates describing the facts section in the facts section of your program, and you use these predicates the same way you use the ones declared in the predicates section.

In Visual Prolog, you use the the predicates assert, asserta, assertz to add new facts to the facts section, and the predicates retract and retractall to remove existing facts. You can modify the contents of your facts section by first retracting a fact and then asserting the new version of that fact (or a different fact altogether). The predicate consult reads facts from a file and asserts them into the internal facts, and save saves the contents of an internal facts section to a file.

Visual Prolog treats facts belonging to facts sections differently from the way it treats normal predicates. Facts for the facts section predicates are kept in tables, which are easy to modify, while the normal predicates are compiled to binary code for maximum speed.

 

Declaring the facts-sections

The keyword facts or (database) marks the beginning of a sequence of declarations for predicates describing an facts-section. You can add facts--but not rules--to a facts-section from the keyboard at run time with asserta and assertz. Or, by calling the standard predicate consult, you can retrieve the added facts from a disk file. The facts section looks something like the following example.

DOMAINS
    name, address = string
    age = integer
    gender = male ; female

FACTS
    person(name, address, age, gender)

PREDICATES
    male(name, address, age)
    female(name, address, age)
    child(name, age, gender)

CLAUSES

    male(Name, Address, Age) :-
    person(Name, Address, Age, male).

In this example, you can use the predicate person the same way you use the other predicates, (male, female, child); the only difference is that you can insert and remove facts for person while the program is running.

There are two restrictions on using predicates in facts sections:

1.     You can add them into the factssection as facts only--not as rules.

2.     Facts in factssections may not have free variables.

It is possible to have several facts sections, but in order to do this, you must explicitly name each facts section.

    FACTS - mydatabase
        myFirstRelation(integer)
        mySecondRelation(real, string)
        myThirdRelation(string)
        /* etc. */

This declaration creates a factssection with the name mydatabase. If you don't supply a name for an facts database, it defaults to the standard name dbasedom.

The names of predicates in a facts section must be unique within a module (source file), you can't use the same predicate name in two different facts sections. However, the predicates in the named facts sections are private to the module in which they're declared, and won't interfere with predicates in other modules. Modules are explained in the chapter 17.

1. Using the facts sections

Because Visual Prolog represents a relational facts sections as a collection of facts, you can use it as a powerful query language for databases. Visual Prolog's unification algorithm automatically selects facts with the correct values for the known arguments and assigns values to any unknown arguments, while its backtracking algorithm can give all the solutions to a given query.

2. Accessing the facts sections

Predicates belonging to a facts section are accessed in exactly the same way as other predicates. The only visible difference in your program is that the declarations for the predicates are in a facts section instead of a predicates section. Given for instance the following:

you can call person with the goal person(Name,'F') to find all women, or person("Maggie",'F') to verify that there is a woman called Maggie in your facts section.

You should be aware that, by their very nature, predicates in factssections are always nondeterministic. Because facts can be added anytime at run time, the compiler must always assume that it's possible to find alternative solutions during backtracking. If you have a predicate in a factssection for which you'll never have more than one fact, you can override this by prefacing the declaration with the compiler directive determ to the declaration:

    FACTS
       determ daylight_saving(integer)

You will get an error if you try to add a fact for a deterministic database predicate which already has a fact.

3. Updating the facts section

Facts for database predicates can be specified at compile time in the clauses section, as in the example above. At run time, facts can be added and removed by using the predicates described below. Note that facts specified at compile time in the clauses section can be removed too, they're not different from facts added at run time.

Visual Prolog's standard database predicates assert, asserta, assertz, retract, retractall, consult, and save will all take one or two arguments. The optional second argument is the name of an facts section. We describe these predicates in the following pages. The notation "/1" and "/2" after each predicate name refers to the number of arguments that arity version of the predicate takes. The comments after the formats (such as /* (i) */ and /* (o,i) */ show the flow pattern(s) for that predicate.

(1) Adding Facts at Run Time

At run time, facts can be added to the facts sections with the predicates: assert, asserta and assertz, or by loading a file of facts with consult.

There are three predicates to add a single fact at runtime:

    asserta(<the fact>)                                              /* (i) */
    asserta(
<
the fact>, facts_sectionName)               /* (i, i) */
    assertz(
<
the fact>)                                              /* (i) */
    assertz(
<
the fact>, facts_sectionName)               /* (i, i) */
    assert(
<
the fact>)                                                /* (i) */
    assert(
<
the fact>, facts_sectionName)                 /* (i, i) */

asserta asserts a new fact into the facts section before the existing facts for the given predicate, while assertz asserts a new fact after the existing facts for that predicate. assert behaves like assertz.

The assertion predicates always know which facts section to insert the fact in, because the names of the facts section predicates are unique within a program or module. However, you can use the optional second argument for type-checking purposes in order to ensure that you are working on the correct facts section.

The first of the following goals inserts a fact about Suzanne for the person predicate, after all the facts for person currently stored in the facts section. The second inserts a fact about Michael before all the currently-stored facts for person. The third inserts a fact about John after all the other likes facts in the facts section likesDatabase, while the fourth inserts a fact about Shannon in the same facts section, before all the other likes facts.

    assertz(person("Suzanne", "New Haven", 35)).
    asserta(person("Michael", "New York", 26)).
    assertz(likes("John", "money"), likesDatabase).
    asserta(likes("Shannon", "hard work"), likesDatabase).

After these calls the facts sections look as if you'd started with the following facts:

    /* Facts section -- dbasedom */
    person("Michael", "New York", 26).
    /* ... other person facts ... */
    person("Suzanne", "New Haven", 35).
    /* Facts section -- likesDatabase */
    likes("Shannon", "hard work").
    /* ... other likes facts ... */
    likes("John", "money").

Be careful that you don't accidentally write code asserting the same fact twice. The facts sections don't impose any kind of uniqueness, and the same fact may appear many times in a facts section. However, a uniqueness-testing version of assert is very easy to write:

FACTS - people
    person(string,string)

PREDICATES
    uassert(people)

CLAUSES
    uassert(person(Name,Address)):-
        person(Name,Address), ! ;       % OR
        assert(person(Name,Address)).

Loading Facts from a File at Run Time

consult reads in a file, fileName, containing facts declared in a facts section and asserts them at the end) of the appropriate facts section. consult takes one or two arguments:

    consult(fileName) /* (i) */
    consult(fileName, databaseName) /* (i, i) */

Unlike assertz, if you call consult with only one argument (no facts section name), it will only read facts that were declared in the default dbasedom facts section section.

If you call consult with two arguments (the file name and a facts section name), it will only consult facts from that named facts section. If the file contains anything other than a fact belonging to the specified facts section, consult will return an error when it reaches that part of the file.

Keep in mind that the consult predicate reads one fact at a time; if the file has ten facts, and the seventh fact has some syntax error, consult will insert the first six facts into the facts section--then issue an error message.

Note that consult is only able to read a file in exactly the same format as save generates (in order to insert facts as fast as possible). There can be

no upper-case characters except in double-quoted strings

no spaces except in double-quoted strings

no comments

no empty lines

no symbols without double quotes

You should be careful when modifying or creating such a file of facts with an editor.

(2) Removing Facts at Run Time

retract unifies facts and removes them from the facts sections. It's of the following form:

    retract(<the fact>[, databaseName])                 /* (i, i) */

retract will remove the first fact in your facts section that matches <the fact>, instantiating any free variables in <the fact> in the process. Retracting facts from a facts section is exactly like accessing it, with the side-effect that the matched fact is removed. Unless the facts section predicate accessed by retract was declared to be deterministic, retract is nondeterministic and will, during backtracking, remove and return the remaining matching facts, one at a time. When all matching facts have been removed, retract fails.

Suppose you have the following facts sections in your program:

Armed with these facts sections, you give Visual Prolog the following goals:

    retract(person("Fred", _, _)).                         /* 1 */
    retract(likes(_, "broccoli")).
                           /* 2 */
    retract(likes(_, "money"), likesDatabase).
        /* 3 */
    retract(person("Fred", _, _), likesDatabase)     /* 4 */

The first goal retracts the first fact for person about Fred from the default dbasedom facts section. The second goal retracts the first fact matching likes(X, "broccoli") from the facts section likesDatabase. With both of these goals, Visual Prolog knows which facts section to retract from because the names of the facts section predicates are unique: person is only in the default facts section, and likes is only in the facts section likesDatabase.

The third and fourth goals illustrate how you can use the optional second argument for type-checking. The third goal succeeds, retracting the first fact that matches likes(_, "money") from likesDatabase, but the fourth cannot be compiled because there are (and can be) no person facts in the facts section likesDatabase. The error message given by the compiler is:

    506 Type error: The functor does not belong to the domain.

The following goal illustrates how you can obtain values from retract:

    GOAL
        retract(person(Name, Age)),
        write(Name, ", ", Age),
        fail.

If you supply the name of a facts section section as the second argument to retract, you don't have to specify the name of the facts section predicate you're retracting from. In this case, retract will find and remove all facts in the specified facts section. Here's an example:

    GOAL
        retract(X, mydatabase),
        write(X),
        fail.

Removing Several Facts at Once

retractall removes all facts that match <the fact> from your facts section, and is of the following form:

    retractall(<the fact>[, databaseName])

retractall behaves as if defined by

    retractall(X):- retract(X), fail.
    retractall(_).

but it's considerably faster than the above.

As you can gather, retractall always succeeds exactly once, and you can't obtain output values from retractall. This means that, as with not, you must use underscores for free variables.

As with assert and retract, you can use the optional second argument for type-checking. And, as with retract, if you call retractall with an underscore, it can remove all the facts from a given facts section.

The following goal removes all the facts about males from a database of person facts:

    retractall(person(_, _, _, male)).

The next goal removes all the facts from the facts section mydatabase.

    retractall(_, mydatabase).

4. Facts determiner-keywords

Facts can be declared with several optional keywords:

NONDETERM    determines that any number of instances of a fact fact_N can exist. This is default.

DETERM          determines that only one instance of a fact fact_N can exist at any time.

GLOBAL          determines, that the facts section is global in the project.

SINGLE           determines, only one instance of a fact fact_N should always exist. Fact_N is the functors for the facts (predicates) belonging to this facts section.

NOCOPY        determins, that dates are not copied from the heap to the Visual Prolog Global Stack (GStack), when the fact is referenced. Normally, when calling a fact to bind a variable to a string or a compound object, the string or object is copied to the Gstack.

(1) Discussions

Facts declared with the keyword nondeterm.

The keyword nondeterm is the default type for facts (database predicates) declared in facts sections. If none of the keywords determ or single are used in a fact declaration, the compiler applies nondeterm keyword. Normally, by their very nature, database predicates are non-deterministic. Because facts can be added anytime at runtime, the compiler must always assume that it's possible to find alternative solutions during backtracking.

If you have a database predicate of which you'll never have more than one fact, you can override this by adding the keyword determ or single to the declaration.

Facts declared with the keyword determ.

The keyword determ determins that the facts database can only contain one instance of a fact (database predicate) fact_N(...) declared with this keyword. So if you try to assert one and then a second such fact into the database, the Visual Prolog engine will generate runtime error. (1041 Assert to a fact declared as determ, but fact already exists). In such cases, programmer must take special care about this.

Preceding a fact with determ enables the compiler to produce better code, and you will not get non-deterministic warnings for calling such a predicate. This is useful for flags, counters, and other things that are essentially global variables.

Particularly note that when retracting a fact that is declared to be determ, the call to non-deterministic predicates retract/1 and retract/2 will be deterministic. So if you know that at any moment the facts section contains no more then one fact counter() then you can write:

    FACTS
    determ counter(integer CounterValue)
    GOAL
    ...
    retract(counter(CurrentCount)),
    /* here Prolog will not set backtracking point */
    Count= CurrentCount + 1,
    assert(counter(Count)),
...

instead of

    FACTS
    counter(integer CounterValue)
    PREDICATES
    determ my_retract(dbasedom)
    CLAUSES
    my_retract(X): - retract(X),!. % deterministic predicate
    GOAL
    ...
    my_retract(counter(CurrentCount)),
    /* here Prolog will not set backtracking point */
    Count= CurrentCount + 1,
    asserta(counter(Count)),
    ...

Facts declared with the keyword single.

The keyword single before a fact fact_N declaration determines that one and only one instance of a fact must always exist:

Since single facts must be already known when the program calls Goal; therefore, single facts must be initialized in a clauses section in the program's source code. For example:

    FACTS
    single singleFact(STRING, STRING)
    CLAUSES
    singleFact("","").

·Single facts cannot be retracted. If one try to apply any retract predicate to a single fact then the compiler will generates the error 249 "Attempt to retract a fact declared as single".·Since one instance of a single fact always exists, a single fact never fails if it is called with free arguments. For example, a following call

    singleFact(X,Y),

never fails if X and Y are free variables. Therefore, it is convenient to use single facts in procedures.assert, asserta, assertz, and consult predicates applied to a single fact act similarly to couples of retract and assert predicates. That is, assert (consult) predicates change the existing instance of a fact to the specified one.

Preceding a fact with single enables the compiler to produce optimized code for accessing and updating of a fact. For example, for assert predicate applied to a single fact the compiler generates a code that works more effectively that a couple of retract and assert predicates applied to a determ fact (and all the more so then retract and assert predicates applied to a nondeterm fact).

5. Saving a database of facts at runtime

save saves facts from a given facts section to a file. save takes one or two arguments:

    save(fileName)                                          /* (i) */
    save(fileName, databaseName)                   /* (i, i) */

If you call save with only one argument (no facts section name), it will save the facts from the default dbasedom database to the file fileName.

If you call save with two arguments (the file name and a facts section name), it will save all facts of the facts section databaseName to the named file.

Examples

1.  This is a simple example of how to write a classification expert system using the facts section. The important advantage of using the facts section in this example is that you can add knowledge to (and delete it from) the program at run time.

/* Program ch08e01.pro */

The following database facts could have been asserted using asserta or assertz, or consulted from a file using consult. In this example, however, they're listed in the clauses section.

    is_a(language, tool, ["communicate"]).
    is_a(hammer, tool, ["build a house", "fix a fender", "crack a nut"]).
    is_a(sewing_machine, tool, ["make clothing", "repair sails"]).
    is_a(plow, tool, ["prepare fields", "farm"]).
    type_of(english, language, ["communicate with people"]).
    type_of(prolog, language, ["communicate with a computer"]).

As the goal enter:

    run(tool).

Respond to each question as if you were looking for some tool to communicate with a personal computer.

Now enter the following goal:

    update, run(tool).

The update predicate is included in the source code for the program, to save you a lot of typing, and will remove the fact

type_of(prolog, language, ["communicate with a computer"])

from the facts section and add two new facts into it:

    type_of(prolog, language,
               ["communicate with a mainframe computer"]).
    type_of("Visual Prolog
", language,
    ["communicate with a personal computer"]).

Now respond to each question once again as if you were looking for some tool to communicate with a personal computer.

You can save the whole facts database in a text file by calling the predicate save with the name of the text file as its argument. For example, after the call to

    save("mydata.dba")

the file mydata.dba will resemble the clauses section of an ordinary Visual Prolog program, with a fact on each line. You can read this file into memory later using the consult predicate:

    consult("mydata.dba")

2.  You can manipulate facts describing database predicates (facts declared in the facts section of your program) as though they were terms.

When you declare a facts section, Visual Prolog will internally generate a domain definition corresponding to the facts declaration. As an example, consider the declarations

    FACTS - dba1     /* dba1 is the domain for these predicates */
       person(name, telno)
   
    city(cno, cname)

Given these declarations, the Visual Prolog system internally generates the corresponding dba1 domain:

    DOMAINS
   
    dba1 = person(name, telno) ; city(cno, cname)

This dba1 domain can be used like any other predefined domain. For example, you could use the standard predicate readterm (which is covered in chapter 12) to construct a predicate my_consult, similar to the standard predicate consult.

Program 2 illustrates one practical way you might use the facts section in an application. This example uses a screen handler, which places text on the screen in predefined locations. A screen layout for the current screen display can be stored in the field and textfield facts that are defined in the screen facts section. Several screen names can be stored in the screens facts section. At run time, the shiftscreen predicate can copy one of these stored screens to the screen facts section by first retracting all current data from the screen facts section, calling the screen predicate to get the layout information for the upcoming screen, then asserting the new screen's form into the screen facts section.

/* Program ch08e02.pro */

 

Summary

 

1.   Visual Prolog's facts section is composed of the facts in your program that are grouped into facts sections. You declare the user-defined predicates used in these groups of facts with the keyword facts.

2.   You can name facts sections (which creates a corresponding internal domain); the default domain for (unnamed) facts sections is dbasedom. Your program can have multiple facts sections, but each one must have a unique name. You can declare a given facts predicate in only one facts section.

3.   With the standard predicates assert, asserta, assertz, and consult, you can add facts to the facts section at run time. You can remove such facts at run time with the standard predicates retract and retractall.

4.  The save predicate saves facts from a facts section to a file (in a specific format). You can create or edit such a fact file with an editor, then insert facts from the file into your running program with consult.

5.  You can call database predicates in your program just like you call other predicates.

6.  You can handle facts as terms when using the domain internally generated for a database section.