External Database Programming

In this section, we provide seven examples that illustrate some general principles and methods for working with Visual Prolog's external database system. This is a summary of what the following sections cover:

"Scanning through a Database" shows you the way to perform a sequential scan through a chain or a B+ tree in an external database.

"Displaying the Contents of a Database" defines a predicate you can use to display the current state of an external database.

"Making a Database That Won't Break Down" illustrates how to protect your database from unexpected system power failure and other potential catastrophes.

"Updating the Database" provides an example that makes it easy to change, add to, and protect your database.

"Using Internal B+ Tree Pointers" supplies you with some predicates for positioning a pointer within an open B+ tree.

"Changing the Structure of a Database" offers an alternative to the old copy-while-changing method of changing the structure of a database.

1. Scanning through a Database

When you are using the database system, it is important to keep Visual Prolog's storage mechanisms storage mechanisms in mind. Every time Visual Prolog retrieves a term from an external database with the ref_term predicate, it places that term on the global stack. The system won't release the space occupied by that term until the program fails and backtracks to a point before the call to ref_term. This means that, to do a sequential scan through a chain in an external database, you should always use a structure like the following:

 

scanloop(db_selector, Ref) :-

    ref_term(db_selector, mydom, Ref, Term),

    /* ... do your processing ... */

    fail.

 

scanloop(db_selector, _) :-

    chain_next(db_selector, Ref, NextRef),

    scanloop(db_selector, NextRef).

Similarly, for a sequential scan through an index, you should use a structure like this:

 

scan(db_selector, Bt_selector) :-

    key_first(db_selector, Bt_selector, FirstRef),

    scanloop(db_selector, Bt_selector, FirstRef).

 

scanloop(db_selector, Bt_selector, Ref) :-

    ref_term(db_selector, mydom, Ref, Term),

    /* ... do your processing ... */

    fail.

 

scanloop(db_selector, Bt_selector, _) :-

    key_next(db_selector, Bt_selector, NextRef),

    scanloop(db_selector, Bt_selector, NextRef).

You can also carry out a sequential scan through a chain in the database by using chain_terms, like this:

 

scan(db_selector, Chain) :-

    chain_terms(db_selector, Chain, mydom, Term, Ref),

/* ... do your processing ... */

    fail.

scan(_, _).

To scan through a B+ tree, you could have also defined and used the predicate bt_keys. During backtracking, this predicate returns (for a given B+ tree and database) each key in the tree and its associated database reference number.

/* This fragment goes with Program 5 */

    bt_keysloop(Db_selector, Bt_selector, Key, Ref):-
        key_current(Db_selector, Bt_selector, Key, Ref).

    bt_keysloop(Db_selector, Bt_selector, Key, Ref):-
        key_next(Db_selector, Bt_selector, _),
        bt_keysloop(Db_selector, Bt_selector, Key, Ref).

2. Displaying the Contents of a Database

You can use the predicate listdba, defined in the following program fragment, to display the current state of an external database. listdba has one argument: the selector of a database assumed to be open. All terms in the database must belong to the same domain. In the example, the domain is called mydom; when you use this predicate, you must replace mydom with the actual name of the appropriate domain in your program.

/* Program ch14e05.pro */

 

DOMAINS

    db_selector = mydba

    mydom = city(zipcode, cityname);

                 person(firstname, lastname, street, zipcode, code)

    zipcode, cityname, firstname, lastname, street, code  =  string

 

PREDICATES

    listdba(db_selector)

    nondeterm bt_keys(db_selector,bt_selector,string,ref)

    nondeterm bt_keysloop(db_selector,bt_selector,string,ref)

 

CLAUSES

    listdba(Db_selector):-nl,

        write("********************************************"),nl,

        write("           DATABASE LISTING"),nl,

        write("********************************************"),

        db_statistics(Db_selector,NoOfTerms,MemSize,DbaSize,FreeSize),nl,nl,

        write("Total number of records in the database: ",NoOfTerms),nl,

        write("Number of bytes used in main memory: ",MemSize),nl,

        write("Number of bytes used by the database: ",DbaSize),nl,

        write("Number of bytes free on disk: ",FreeSize),nl,

        fail.

 

    listdba(Db_selector):-

        db_chains(Db_selector,Chain),nl,nl,nl,nl,

        write("******* Chain LISTING *************"),nl,nl,

        write("Name=",Chain),nl,nl,

        write("CONTENT OF: ",Chain),nl,

        write("------------------------------ˇ¬n"),

        chain_terms(Db_selector, Chain, mydom,Term, Ref),

        write("ˇ¬n", Ref, ": ",Term),

        fail.

 

    listdba(Db_selector):-

    db_btrees(Db_selector,Btree),     /* Returns each B+ tree name */

        bt_open(Db_selector,Btree,Bt_selector),

        bt_statistics(Db_selector,Bt_selector,NoOfKeys,

                          NoOfPages,Dept,KeyLen,Order,PageSize),nl,nl,nl,

        write("******** INDEX LISTING **************"),nl,nl,

        write("Name=     ", Btree),nl,

        write("NoOfKeys= ", NoOfKeys),nl,

        write("NoOfPages=", NoOfPages),nl,

        write("Dept=     ", Dept),nl,

        write("Order=    ", Order),nl,

        write("KeyLen=   ", KeyLen),nl,

        write("PageSize= ", PageSize), nl,

        write("CONTENT OF: ", Btree),nl,

        write("-----------------------------ˇ¬n"),

        bt_keys(Db_selector,Bt_selector,Key,Ref),

        write("ˇ¬n",Key, " - ",Ref),

        fail.

listdba(_).

 

bt_keys(Db_selector,Bt_selector,Key, Ref):-

    key_first(Db_selector,Bt_selector,_),

    bt_keysloop(Db_selector,Bt_selector,Key,Ref).

 

bt_keysloop(Db_selector,Bt_selector,Key,Ref):-

    key_current(Db_selector,Bt_selector,Key,Ref).

 

bt_keysloop(Db_selector,Bt_selector,Key,Ref):-

    key_next(Db_selector,Bt_selector,_),

bt_keysloop(Db_selector,Bt_selector,Key,Ref).

 

GOAL

        db_open(mydba,filename,in_file),

        listdba(mydba).

3. Implementing a Database That Won't Break Down

If you enter a lot of new information into a database, it is important to ensure that this information won't be lost if the system goes down. In this section, we illustrate one way of doing this -- by logging all changes in another file.

Making a change involves first updating the database, and then flushing it. If this operation succeeds, the system then records the change in the log file and flushes the log file itself. This means that only one file is unsafe at any given time. If the database file becomes invalid (because the system went down before the file was flushed, for example), you should be able to reconstruct it by merging the log file with a backup of the database file. If the log file becomes invalid, you should create a new log file and make a backup of the database file.

If you record the date and time in the log file, together with the old values from a modification involving replacement or deletion, you should be able to reconstruct the database to its state at a given time.

/* This program fragment goes with Program 6 */

 

PREDICATES

    logdbchange(logdom)

 

CLAUSES

    logdbchange(Logterm):-

        chain_insertz(logdba,logchain,logdom,Logterm,_),

        db_flush(logdba).

4. Updating the Database

As a general principle, you shouldn't spread database updating throughout the program but should keep it in some user-defined predicates. This makes it easier to change the database and/or to add new B+ trees. When you confine updating this way, it's also easier to make a robust database system because your program involves only a small piece of code in which the database is unsafe.

The following example handles updating two different relations, whose objects are all strings:

    person(firstname, lastname, street, zipcode, code)
    city(zipcode, cityname)

It handles the updating with the following indexes (keys) on the person and city relations:

    Person's Name.............Last Name plus First Name
    Person's Address.........Street Name
    City Number.................Zip Code

In this example, we assume that the B+ trees are already open, and that their bt_selectors have been asserted in the database predicate indices.

Before this program initiates the updating, it eliminates the possibility of a BREAK with the break predicate. After updating is finished, the program flushes the database with db_flush. Although db_flush makes the updating a slow process (thanks to DOS), the file will be safe after this call.

To make the system as secure as possible, the program logs changes in a special file through a call to logdbchange.

/* Program ch14e06.pro */

DOMAINS

    logdom = insert(relation,dbdom,ref);

    replace(relation,dbdom,ref,dbdom);

    erase(relation,ref,dbdom)

 

PREDICATES

    logdbchange(logdom)

 

CLAUSES

    logdbchange(Logterm):-

        chain_insertz(logdba,logchain,logdom,Logterm,_),

        db_flush(logdba).

 

DOMAINS

    dbdom = city(zipcode, cityname);

    person(firstname, lastname, street, zipcode, code)

    zipcode, cityname, firstname, lastname = string

    street, code = string

    indexName = person_name; person_adr; city_no

    relation  = city; person

    db_selector = dba; logdba

 

DATABASE

    % This takes and index name (a key) that is a person's name or address

    %or a city number; it also takes a B+ tree selector

    indices(IndexName, bt_selector)

 

PREDICATES

    %and a first name (10 characters)

    % This predicate creates an index name from a last name (20 characters)

    xname(FirstName,LastName,string)

 

CLAUSES

    xname(F,L,S):-

        str_len(L,LEN),LEN>20,!,

        frontstr(20,L,L1,_),

        format(S,"%-20%",L1,F).

    xname(F,L,S):-

    format(S,"%-20%",L,F).

 

PREDICATES

    ba_insert(relation, dbdom)

    dba_replace(relation, dbdom, Ref)

    dba_erase(relation, Ref)

 

CLAUSES

    dba_insert(person,Term):-!,

        break(OldBreak),

        break(off),

        indices(person_name,I1),

        indices(person_adr,I2),!,

        Term = person(Fname,Lname,Adr,_,_),

        xname(Fname,Lname,Xname),

        chain_insertz(dba,person,dbdom,Term,Ref),

        key_insert(dba,I1,Xname,Ref),

        key_insert(dba,I2,Adr,Ref),

        db_flush(dba),

        logdbchange(insert(person,Term,Ref)),

        break(OldBreak).

 

    dba_insert(city,Term):-

        break(OldBreak),

        break(off),

        indices(city_no,I),!,

        Term = city(ZipCode,_),

        chain_insertz(dba,city,dbdom,Term,Ref),

        key_insert(dba,I,ZipCode,Ref),

        db_flush(dba),

        logdbchange(insert(city,Term,Ref)),

        break(OldBreak).

 

    dba_replace(person,NewTerm,Ref):-!,

        break(OldBreak),

        break(off),

        indices(person_name,I1),

        indices(person_adr,I2),!,

        ref_term(dba,dbdom,Ref,OldTerm),

        OldTerm=person(OldFname,OldLname,OldAdr,_,_),

        xname(OldFname,OldLname,OldXname),

        key_delete(dba,I1,OldXname,Ref),

        key_delete(dba,I2,Oldadr,Ref),

        NewTerm=person(NewFname,NewLname,NewAdr,_,_),

        xname(NewFname,NewLname,NewXname),

        term_replace(dba,dbdom,Ref,NewTerm),

        key_insert(dba,I1,NewXname,Ref),

        key_insert(dba,I2,NewAdr,Ref),

        db_flush(dba),

        logdbchange(replace(person,NewTerm,Ref,OldTerm)),

        break(OldBreak).

 

    dba_replace(city,NewTerm,Ref):-!,

        break(OldBreak),

        break(off),

        indices(city_no,I),!,

        ref_term(dba,dbdom,Ref,OldTerm),

        OldTerm=city(OldZipCode,_),

        key_delete(dba,I,OldZipCode,Ref),

        NewTerm=city(ZipCode,_),

        term_replace(dba,dbdom,Ref,NewTerm),

        key_insert(dba,I,ZipCode,Ref),

        db_flush(dba),

        logdbchange(replace(city,NewTerm,Ref,OldTerm)),

        break(OldBreak).

 

    dba_erase(person,Ref):-!,

        break(OldBreak),

        break(off),

        indices(person_name,I1),

        indices(person_adr,I2),!,

        ref_term(dba, dbdom, Ref, OldTerm),

        OldTerm=person(OldFname,OldLname,OldAdr,_,_),

        xname(OldFname,OldLname,OldXname),

        key_delete(dba,I1,OldXname,Ref),

        key_delete(dba,I2,OldAdr,Ref),

        term_delete(dba,person,Ref),

        db_flush(dba),

        logdbchange(erase(person, Ref, OldTerm)),

        break(OldBreak).

 

    dba_erase(city,Ref):-

        break(OldBreak),

        break(off),

        indices(city_no,I),!,

        ref_term(dba,dbdom,Ref,OldTerm),

        OldTerm=city(OldZipCode,_),

        key_delete(dba,I,OldZipCode,Ref),

        term_delete(dba,city,Ref),

        db_flush(dba),

        logdbchange(erase(city,Ref,OldTerm)),

        break(OldBreak).

5. Using Internal B+ Tree Pointers

Each open B+ tree has an associated pointer to its nodes. When you open or update the B+ tree, this pointer is positioned before the start of the tree. When you call key_next with the pointer at the last key in the tree, the pointer will be positioned after the end of the tree. Whenever the pointer moves outside the tree, key_current fails. If this arrangement is not appropriate for a particular application, you can model other predicates.

You can use mykey_next, mykey_prev, and mykey_search, defined in this example, to ensure that the B+ tree pointer is always positioned inside the B+ tree (provided there are any keys in the tree).

    PREDICATES
       mykey_next(db_selector, bt_selector, ref)
       mykey_prev(db_selector, bt_selector, ref)
       mykey_search(db_selector, bt_selector, string, ref)

    CLAUSES
        mykey_prev(Dba, Bt_selector, Ref) :-
            key_prev(Dba, Bt_selector, Ref), !.
        mykey_prev(Dba, Bt_selector, Ref) :-
            key_next(Dba, Bt_selector, Ref), fail.

        mykey_next(Dba, Bt_selector, Ref) :-
           key_next(Dba, Bt_selector, Ref), !.
        mykey_next(Dba, Bt_selector, Ref) :-
           key_prev(Dba, Bt_selector, Ref), fail.

        mykey_search(Dba, Bt_selector, Key, Ref) :-
            key_search(Dba, Bt_selector, Key, Ref), !.
        mykey_search(Dba, Bt_selector, _, Ref) :-
            key_current(Dba, Bt_selector, _, Ref), !.
        mykey_search(Dba, Bt_selector, _, Ref) :-
            key_last(Dba, Bt_selector, Ref).

You can use the samekey_next and samekey_prev predicates, defined in the next example, to move the index pointer to the next identical key in a B+ tree that has duplicate keys.

     samekey_next(db_selector, bt_selector, ref)

try_next(db_selector, bt_selector, ref, string)

    samekey_prev(db_selector, bt_selector, ref)

    try_prev(db_selector, bt_selector, ref, string)

 

CLAUSES

    Samekey_next(Dba, Bt_selector, Ref) :-

        key_current(Dba, Bt_selector, OldKey, _),

        try_next(Dba, Bt_selector, Ref, OldKey).

    try_next(Dba, Bt_selector, Ref, OldKey) :-

        key_next(Dba, Bt_selector, Ref),

        key_current(Dba, Bt_selector, NewKey, _),

        NewKey = OldKey, !.

 

    try_next(Dba, Bt_selector, _, _) :-

        key_prev(Dba, Bt_selector, _),

        fail.

 

    samekey_prev(Dba, Bt_selector, Ref) :-

        key_current(Dba, Bt_selector, OldKey, _),

        try_prev(Dba, Bt_selector, Ref, OldKey).

    try_prev(Dba, Bt_selector, Ref, OldKey) :-

        key_prev(Dba, Bt_selector, Ref),

        key_current(Dba, Bt_selector, NewKey, _),

        NewKey = OldKey, !.

 

    try_prev(Dba, Bt_selector, _, _) :-

        key_next(Dba, Bt_selector, _),

        fail.

6. Changing the Structure of a Database

One way to change the structure of a database is to write a small program that copies the old database to a new one while making external databases, changing structure of the changes. Another way, which we'll describe here, is to first dump the database into a text file, make any necessary modifications to the database with a text editor, and then read the modified database back into a new file.

You can use the predicate dumpDba, defined in the next program fragment, to dump the contents of an external database into a text file if the database satisfies the following conditions:

Every chain in the database models a relation.

All terms in the database belong to the same domain.

This method does not dump the B+ trees into the text file; we assume, given the first condition, that B+ trees can be generated from the relations. In this example, all terms belong to the generic domain mydom; when you implement this method, replace mydom with the actual name and a proper declaration.

This code writes the contents of the database to a text file opened by outfile. Each line of the text file contains a term and the name of the containing chain. The term and the chain names are combined into the domain chainterm.

/* Program ch14e07.pro */

 

DOMAINS

    Db_selector = myDba

    chainterm  = chain(string, mydom)

    file = outfile

    mydom = city(zipcode, cityname);

    person(firstname, lastname, street, zipcode, code)

    zipcode, cityname, firstname, lastname = string

    street, code = string

 

PREDICATES

    wr(chainterm)

    dumpDba(string,string)

 

CLAUSES

    wr(X):-

        write(X),nl.

 

    dumpDba(Db_selector,OutFile):-

        db_open(myDba,Db_selector,in_file),

        openwrite(outfile,OutFile),

        writedevice(outfile),

        db_chains(myDba,Chain),

        chain_terms(myDba,Chain,mydom,Term,_),

        wr(chain(Chain,Term)),

        fail.

 

    dumpDba(_,_):-

        closefile(outfile),

        db_close(myDba).

 

GOAL

    dumpDba(filename,"register.txt").

Now, using your customized version of this code, you can generate the text file by calling dumpDba, and you can reload the database by using readterm with the chainterm domain. The predicate dba_insert, which we defined in "Updating the Database" (page 205), takes care of the updating.

 

PREDICATES

    nondeterm repfile(file)

    copyDba

    loadDba(string)

 

CLAUSES

    repfile(_).

repfile(File) :- not(eof(File)), repfile(File).

 

loadDba(OutFile) :-

    openread(Prn_file, OutFile),

    readdevice(Prn_file),

    repfile(Prn_file),

    readterm(Chainterm, chain(Chain, Term)),

    write(Term), nl,

    Dba_insert(Chain, Term),

    fail.

 

    closefile(Prn_file).

 

copyDba :-

    createDba,

    db_open(Dba, "register.bin", in_file),

    open_indices,

    loadDba("register.txt"),

    db_close(Dba).

7. Filesharing and the External Database

Visual Prolog supports file-sharing the external database. This means that a file can be opened by several users or processes simultaneously, which will be useful if you are using the external database in a LAN-application or with one of the multitasking platforms. UNIX developers should take note that Visual Prolog uses advisory filelocking.

Visual Prolog provides the following file-sharing facilities:

opening an existing database with two different access modes and three different sharing modes for optimal speed.

grouping database accesses in transactions to ensure consistency

predicates that make it possible to check whether other users have updated the database.

8. Filesharing Domains

The two special domains which are used for file-sharing have the alternatives:

Domain

Functors

accessmode

= read; readwrite

denymode

= denynone; denywrite; denyall

9. Opening the Database in Sharemode

In order to access the external database in share mode, you must open an already existing database file with the four arity version of db_open, specifying AccessMode and DenyMode.

If AccessMode is read the file will be opened as readonly, and any attempts to update the file will result in an run-time error, if it is readwrite the file is opened for both reading and writing. AccessMode is also used with the predicate db_begintransaction.

If DenyMode is denynone all other users will be able to both update and read the file, if it is denywrite, other users will not be able to open the file in accessmode = readwrite, but you will be able to update the file providing it was opened in accessmode = readwrite. If db_open is called with denymode = denyall no other users will be able to access the file at all.

The first user that opens the file determines DenyMode for all subsequent attempts to open the file, and a run-time error will occur if reopened in an incompatible mode. The following table summarizes the results of opening and subsequently attempting to reopen the same file for all combinations of DenyMode and AccessMode:

    2ND, 3RD, ..... REOPEN
    Denyall Denywrite Denynone

    R : AccessMode = read

    RW: AccessMode = readwrite

    Y : Open by 2ND, 3RD .. allowed

    N : Open by 2ND, 3RD .. not allowed

(1) Transactions and Filesharing

If a database file is opened in share mode, all database predicates that access the database file in any way, must be grouped inside "transactions" this is done by surrounding the calls to the predicates  with db_begintransaction and db_endtransaction.

Dependent on the combination of the chosen AccessMode and DenyMode the shared file may be locked for the duration of the transaction. Again dependent on the severity of the lock, other users may not be able to either read or update the file, while your transaction takes place. This is of course necessary to avoid conflicts between reading and writing, but if file-sharing is to have any meaning, no excessive locking ought to take place. This can be avoided by keeping the transactions small (as short as possible) and only include those predicates that access the database inside the transaction.

The concept of transactions in relation to file-sharing is very important. Two often conflicting requirements, namely  database consistency and a minimum of file locking, must be fulfilled at the same time.

db_begintransaction ensures that database consistency is maintained and that an appropriate locking of the file is effectuated. Several readers can access the file at the same time, but only one process at the time is allowed to update the database. The predicate db_setretry can be called to set for how long db_begintransaction will wait to gain access to the file before returning with a run-time error. Calling db_begintransaction with accessmode set to readwrite with a file opened with accessmode set to read will also result in a run-time error. If db_begintransaction is called, db_endtransaction must be called before a new call to db_begintransaction for the same database, otherwise a run-time error will occur.

The following table summarizes the actions taken by db_begintransaction with different combinations of AccessMode and DenyMode:

AccessMode

read readwrite 

DenyMode- denynone WLockˇ¬Reload RWLockˇ¬Reload

    Actions :

    WLock  : No write. Read allowed.
    RWLOCK : No read or write allowed.
    Reload : Reloading of file descriptors.

Since reloading and locking takes time, AccessMode and DenyMode should be selected with care. If no users are going to update the database, set AccessMode to read and DenyMode to denywrite for a minimal overhead.

(2) Filesharing Predicates

In this section we discuss the file sharing predicates db_open, db_begintransaction, db_endtransaction, db_updated, bt_updated, and db_setretry.

(3) db_open/4

This four arity version of db_open opens an existing database on file in share mode.

    db_open(Dbase, Name, AccessMode, DenyMode)        /* (i,i,i,i) */

After creating an external database (in_file)­ with db_create it can be opened in share mode, where Dbase is a db_selector, Name is the DOS-style file name, AccessMode is read or readwrite, and DenyMode is denynone, denywrite, or denyall.

(4) db_begintransaction/2

    db_begintransaction(Dbase, AccessMode)                /* (i,i) */

This predicate marks the beginning of a transaction, and must be called prior to any form of access to a database opened in share mode, even if opened with denyall. In addition to the db_selector for the database, db_begintransaction must be called with AccessMode bound to either read or readwrite.

(5) db_endtransaction/1

    db_endtransaction(Dbase)                                /* (i) */

db_endtransaction marks the end of a transaction and carries out the appropriate unlocking of the database. A call of db_endtransaction without a prior call to db_begintransaction for the db_selector Dbase will result in an run-time error.

(6) db_updated/1

    db_updated(Dbase)                                       /* (i) */

If other users have updated the database, a call of db_begintransaction will ensure that database consistency is maintained. Changes can be detected with the predicate db_updated, which succeeds if called inside a transaction where changes made by other users since your last call of db_begintransaction. If no changes have been made, db_updated will fail. If called outside a transaction a run-time error will occur.

(7) bt_updated/2

    bt_updated(Dbase,Btree_Sel)                          /* (i,i) */

Similar to db_updated/1, but only succeeds if the named B+ tree has been updated.

(8) db_setretry/3

    db_setretry(Dbase,SleepPeriod,RetryCount)          /* (i,i,i) */

If access to a file is denied, because another process has locked the file, you can have your process wait for a period of time and then try again. The predicate db_setretry changes the default settings of SleepPeriod, which is the interval in centiseconds between retries, and RetryCount, which is the maximum number of times access will be attempted. The default settings are 100 for RetryCount and 10 for SleepPeriod.

10. Programming with Filesharing

Great care must be taken when using the file sharing predicates. Although they, when used properly, ensure low-level consistency in a shared database, it is the application programmers responsibility to provide the demanded high level consistency for a given application. The term "transaction" is used here for a group of file accesses, but it should be kept in mind that no back out facilities are provided, and that program interruption caused by either software or hardware failure, may cause inconsistencies in the database file.

When several processes share a database, special attention must also be paid to the domains involved. It's crucial that they are identical and use identical alignment.

To avoid unnecessary locking of the database file the transactions should be kept fairly small, in order to ensure that the file will be locked for as short a time as possible. At the same time it is important that predicates used to locate and access an item in the database are grouped inside the same transaction:

    .....
    db_begintransaction(dba,readwrite),
        key_current(dba,firstindex,Key,Ref),
        ref_term(dba,string,Ref,Term),
    db_endtransaction(dba),
    write(Term),
    .....

In this example the predicates key_current and ref_term should not be placed inside different transactions, as the term stored under Ref may be deleted by another user between transactions.

If a B+ tree is updated by another user and the file buffers are reloaded, the B+ tree will be repositioned before the first element of the tree. By calling the predicate bt_updated you can detect when to reposition your B+ tree. It is still possible to list the entire index and at the same time keep the transactions small, by temporarily storing the current key in the internal database, as shown in the following program fragment. It works under the assumption that no duplicate keys exist.

DOMAINS
    db_selector = dba

DATABASE
    determ currentkey(string)

PREDICATES
    list_keys(bt_selector)
    list_index(bt_selector)
    check_update(bt_selector,string)

CLAUSES
    check_update(Index,Key):-
       not(bt_updated(dba,Index)),!,
       key_next(dba,Index,_).
    check_update(Index,Key):-
       key__search(dba,Index,Key,_),!. % Will fail if current was deleted
    check_update(_,_).
                 %by another user

    list_keys(Index):-
        currentkey(Key),
        write(Key),nl,
        db_begintransaction(dba,read),
            check_update(Index,Key),
            key_current(dba,Index,NextKey,_),

        db_endtransaction(dba),!,
        retract(currentkey(_)),
        assert(currentkey(NextKey)),
        list_keys(Index).
    list_keys(_):-
        db_endtransaction(dba).


    list_index(Index):-
        db_begintransaction(dba,read),
            key_first(dba,Index,_),
            key_current(dba,Index,Key,_),
        db_endtransaction(dba),
        retractall(currentkey(_)),
        assert(currentkey(Key)),
        list_keys(Index).
    list_index(_).

key_search is used to reposition the B+ tree at the key that was listed previously. The my_search predicate insures that the B+ tree will be correctly positioned even if currentkey was deleted by another user.

The example above also illustrates another important point. A db_endtransaction must be used after each, and before the next, call of db_begintransaction. In the predicate list_keys above, the listing stops when key_next fails, indicating that all the keys have been listed. As db_begintransaction had to be called prior to accessing the database, db_endtransaction has to be called as well after accessing is completed. The second list_keys-clause ensures that db_endtransaction will be called when key_next fails.

11. Implementing highlevel locking

The examples shown so far have illustrated some of the problems involved in file sharing, and how they can be avoided.

You are allowed to do all the same operations on a shared database file as if you were the only user with access to the file. Grouping the accesses to the file inside db_begintransaction and db_endtransaction ensures that the Visual Prolog system has consistency in its descriptor tables. But on a higher level you must yourself ensure that the various logical constraints you have on your application are conserved over a network with multiple users.

We call this high level locking or application level locking. By using the primitives db_begintransaction and db_endtransaction you have many ways of implementing a high level locking facility.

A common example of where high level locking is needed is in a database system where a user wants to change a record. When he has decided that he wants to change a record he should perform some kind of action so the application will place a lock on that record until the user has finished the changes to the record so the new record can be written back to disk, and the record unlocked.

Some suggestions for implementing an application-level lock of this type are:

Have a special field in that record to tell whether it is locked.

Have a special B+Tree or a chain where you store all references to all the records that are locked by users.

Associated with a REF store a list of references to all records that are locked.

You might need to implement a kind of supervisor mechanism so a special user can unlock locked records.

This was just an example, you might want to implement locking on a higher level like tables or groups of tables, - or knowledge groups etc.

Note: If you want to delete a B+ tree in a database file opened in share mode, it is up to you to ensure by high level locking that no other users have opened this B+ Tree. In the Visual Prolog system there is no check for a B+Tree selector being no longer valid because the B+Tree has been deleted by another user.

12. A Complete Filesharing Example

In the following large example it will be shown how file sharing can be done more easily by implementing your own locking system. If you manage your own locks, needless file locking can be avoided, and other users won't have to wait for access to the file because it is locked.

The example is the file sharing version of the previous 4 example. The program lets several users create, edit, view and delete texts from a single shared file. When creating and editing a text, it will be locked until editing is complete. Other users cannot delete or edit a text while it is locked, but they will be able to view the text. Run the program and experiment with different settings for db_open and db_setretry.

/* Program ch14e08.pro */

 

DOMAINS

    my_dom = f(string)

    db_selector = dba

 

PREDICATES

    nondeterm repeat

    wr_err(integer) 

 

% List texts and their status

    list

    list_texts(bt_selector,bt_selector)

    show_textname(string,bt_selector)

 

CLAUSES

    show_textname(Key,LockIndex):-

        key_search(dba,LockIndex,Key,_),!,

        write("ˇ¬n*",Key).

    show_textname(Key,_):-

        write("ˇ¬n ",Key).

    list_texts(Index,LockIndex) :-

        key_current(dba,Index,Key,_),

        show_textname(Key,LockIndex),

        key_next(dba,Index,_),!,

        list_texts(Index,LockIndex).

    list_texts(_,_).

 

    list:-nl,

        write("***************** TEXTS (*=Locked) *******************"),nl,

        index(Index),

        lockindex(LockIndex),

        key_first(dba,Index,_),!,

        list_texts(Index, LockIndex),nl,

        write("******************************************************"),nl.

    list.

 

    repeat.

    repeat:-repeat.

 

    wr_err(E):-

        errormsg("PROLOG.ERR",E,Errormsg,_),

        write(Errormsg),

        readchar(_).

 

PREDICATES

%Logical locking of files

    lock(string,bt_selector,bt_selector)

 

CLAUSES

    lock(Name,Index,LockIndex):-

        not(key_search(dba,LockIndex,Name,_)),!,

        key_search(dba,Index,Name,Ref),

        key_insert(dba, LockIndex, Name, Ref).

    lock(Name,_,_):-

        db_endtransaction(dba),

        write(Name," is being updated by another user.ˇ¬n Access denied"),

        fail.

 

PREDICATES

    ed(db_selector, bt_selector, bt_selector, string)

    ed1(db_selector, bt_selector, bt_selector, string)

 

CLAUSES

% The ed predicates ensure that the edition will never fail.

    ed(dba,Index,LockIndex,Name):-

        ed1(dba,Index,LockIndex,Name),!.

    ed(_,_,_,_).

 

/* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *

* There are two choices:                                               *

*                                                                                *

* 1) The name already exists - modify the contents of the  *

*  file                                                                          *

* 2) The name is a new name - create a new file               *

* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * /

 

    ed1(dba, Index,LockIndex, Name) :-

        db_begintransaction(dba,readwrite),

        key_search(dba, Index, Name, Ref),!,

        ref_term(dba, string, Ref, Str),

        lock(Name,Index,LockIndex),

        list,

        db_endtransaction(dba),nl,

        write("******************************************************"),nl,

        write("*  EDIT               ",Name,"                     *"),nl,

        write("******************************************************"),nl,

        write(Str),nl,

        write("< Press 'r' to replace this string ; else any key >"),nl,

        readchar(X),X='r',nl,

        write("Enter string and press <ENTER>"),nl,

        readln(Str1),nl,

        db_begintransaction(dba,readwrite),

        term_replace(dba, string, Ref, Str1),

        key_delete(dba, LockIndex, Name, Ref), %unlock

        list,

        db_endtransaction(dba).

 

%New file

    ed1(dba, Index,LockIndex, Name):-

        chain_insertz(dba, file_chain, string, "", Ref),

        key_insert(dba, Index, Name, Ref),

        list,

        db_endtransaction(dba),

        ed1(dba,Index,LockIndex, Name).

 

PREDICATES

    main(db_selector, bt_selector, bt_selector)

    interpret(char, bt_selector, bt_selector)

    check_update_view

    update_view

    get_command(char)

 

CLAUSES

% Loop until 'Q' is pressed

    main(dba,Index,LockIndex) :-

        check_update_view,

        get_command(Command),

        trap(interpret(Command,Index,LockIndex),E,wr_err(E)),!,

        main(dba,Index,LockIndex).

    main(_,_,_).

 

    check_update_view:-

        mark(T),timeout(T),!,

        db_begintransaction(dba,read),

        update_view,

        db_endtransaction(dba),

        marktime(100,Mark),

        retractall(mark(_)),

        assert(mark(Mark)).

    check_update_view.

 

    update_view:-nl,

        write("******* COMMANDS E:Edit V:View D:Delete­Q:Quit *******"),nl,

        write("COMMAND>"),

        db_updated(dba),!,

        list.

    update_view.

 

    get_command(Command):-

        readchar(C),!,

        upper_lower(Command,C),

        write(Command),nl.

    get_command(' ').

 

%interpret commandlineinput

    interpret(' ',_,_):-!.

    interpret('Q',_,_):-!,fail.

    interpret('E',Index,LockIndex):-!,

        write("ˇ¬nFile Name: "),

        readln(Name),nl,

        ed(dba,Index,LockIndex,Name).

    interpret('V',Index,_):-

        write("ˇ¬nFile Name: "),

        readln(Name),nl,

        db_begintransaction(dba,read),

        key_search(dba,Index,Name,Ref),!,

        ref_term(dba,string,Ref,Str),

        db_endtransaction(dba),

        write("******************************************************"),nl,

        write("*      VIEW            ",Name,"                      "),nl,

        write("******************************************************"),nl,

        write(Str),nl.

 

    interpret('V',_,_):-!,

        db_endtransaction(dba).

    interpret('D',Index,_):-

        write("ˇ¬nDelete file: "),

        readln(Name),nl,

        db_begintransaction(dba,readwrite),

        key_search(dba,Index,Name,Ref),!,

        %    not(key_search(dba,LockIndex,Name,_)),!,

        key_delete(dba,Index,Name,Ref),

        term_delete(dba,file_chain,Ref),

        list,

        db_endtransaction(dba).

    interpret('D',_,_):-!,

    db_endtransaction(dba).

    nterpret(_,_,_):-beep.

 

PREDICATES

    open_dbase(bt_selector,bt_selector)

 

CLAUSES

    open_dbase(INDEX,LOCKINDEX):-

        existfile("share.dba"),!,

        db_open(dba, "share.dba",readwrite,denynone),

        db_begintransaction(dba,readwrite),

        bt_open(dba, "locks", LOCKINDEX),

        bt_open(dba, "ndx", INDEX),

        db_endtransaction(dba).

 

    open_dbase(INDEX,LOCKINDEX):-

        db_create(dba,"share.dba" , in_file),

        bt_create(dba, "locks",TEMPLOCKINDEX,20, 4),

        bt_create(dba, "ndx",TEMPINDEX , 20, 4),

        bt_close(dba, TEMPINDEX),

        bt_close(dba, TEMPLOCKINDEX),

        db_close(dba),

        open_dbase(INDEX,LOCKINDEX).

 

GOAL

        open_dbase(INDEX,LOCKINDEX),

        assert(index(INDEX)),

        assert(lockindex(LOCKINDEX)),

        marktime(10,Mark),

        assert(mark(Mark)),

        db_setretry(dba,5,20),

        db_begintransaction(dba,read),

        list,nl,

        db_endtransaction(dba),

        main(dba, INDEX,LOCKINDEX),

        db_begintransaction(dba,read),

        bt_close(dba, INDEX),

        bt_close(dba, LOCKINDEX),

        db_endtransaction(dba),

        db_close(dba).

13. Implementation Aspects of Visual Prolog Filesharing

Filesharing in Visual Prolog is efficient and fast, because only the necessary parts of the database file descriptors are loaded after an update by another user. As was shown earlier in this chapter it is only under certain circumstances that any reloading of file buffers and locking of files has to be done at all, and the complex internal management of the database file ensures that after an update a minimum of disk activity is needed.

The database has a serial number, which is a six byte integer, that is incremented and written to disk each time an update occurs. The db_begintransaction predicate compares the local copy of the serial number with the one on the disk, and if they differ, the descriptors are reloaded. Locking is done in an array with room for 256 readers. When a reader wishes to access the file, an unlocked space is located in this lock array, and locked for the duration of the transaction. This allows several readers to access the file simultaneously. If db_begintransaction is called with AccessMode = readwrite, it will wait until all present readers have unlocked their space, and then lock the entire array, allowing no other users to access the file.