PART 3   Tutorial Chapters 12 -- 17 : Using Visual Prolog.

 

CHAPTER 12    Writing, Reading, and Files

 

In this chapter, we first cover the basic set of built-in predicates for writing and reading. Next we describe how the file system works in Visual Prolog and show how you can redirect both input and output to files. We also discuss the file domain and some predefined files.

Writing and Reading

In these tutorials, most of the Input/Output has been interactive via screen and keyboard. In this section, we provide formal covererage of the standard predicates you use for I/O, including predicates for file operations.

1. Writing

Visual Prolog includes three standard predicates for writing. These predicates are write, nl and writef.

(1) write/* and nl

The predicate write can be called with an arbitrary number of arguments:

    write(Param1, Param2, Param3, ..., ParamN)
                                                                          /* (i, i, i, ..., i) */

These arguments can either be constants from standard domains or they can be variables. If they're variables, they must be input parameters.

The standard predicate nl (for new line) is often used in conjunction with write; it generates a newline on the display screen. For example, the following subgoals:

    pupil(PUPIL, CL),
    write(PUPIL," is in the ",CL," class"),
    nl,
    write("-----------------------------------").

could result in this display:

    Helen Smith is in the fourth class
    ----------------------------------

while this goal:

    ....,
    write("List1= ", L1, ", List2= ", L2 ).

could give:

    List1= [cow,pig,rooster], List2= [1,2,3]

Also, if My_sentence is bound to

    sentence(subject(john),sentence_verb(sleeps))

in the following program

    DOMAINS
        sentence = sentence(subject, sentence_verb)
        subject = subject(symbol) ; ......
        sentence_verb = sentence_verb(verb) ; ......
        verb = symbol

    CLAUSES
        ....
        write( " SENTENCE= ", My_sentence ).

you would obtain this display:

    SENTENCE= sentence(subject(john),sentence_verb(sleeps))

Note that with respect to strings, the backslash (¡¬) is an escape character. To print the backslash character verbatim, you must type two backslashes. For example, to designate the DOS directory path name A:¡¬PROLOG¡¬MYPROJS¡¬MYFILE.PRO in a Visual Prolog program, you would type a:¡¬¡¬prolog¡¬¡¬myprojs¡¬¡¬myfile.pro.

If a backslash is followed by one of a few specially recognized characters, it will be converted to a print control character. These are

'n'     newline and carriage return
't'
     tab
'r'
     carriage return

Alternatively, the backslash may be followed by up to three decimal digits, specifying a particular ASCII code. However, avoid putting ¡¬0 into a string unless you know what you're doing. Visual Prolog uses the C convention with 0- terminated strings.

Be very careful with the '¡¬r' option. It sets the current write position back to the start of the current line, but if you accidentally do that in between writing different things, it may happen so quickly that the first thing you write becomes overwritten before you even notice it's there. Also, if you write something which is too long for a single line, causing the output to wrap, the '¡¬r' will set the cursor back to the beginning of the last line, not the beginning of the line where the writing started.

Often write does not, by itself, give you as much control as you'd like over the printing of compound objects such as lists, but it's easy to write programs that give better control. The following four small examples illustrate the possibilities.

Examples Demonstrating the write Predicate

These examples show how you can use write to customize your own predicates for writing such things as lists and compound data structures.

1. Program ch11e01.pro prints out lists without the opening bracket ([) and closing bracket (]).

/* Program ch12e01.pro */

    /* Copyright (c) 1986, '95 by Prolog Development Center */

DOMAINS
    integerlist = integer*
    namelist
    = symbol*

PREDICATES
    writelist(integerlist)
    writelist(namelist).

CLAUSES
    writelist([]).
    writelist([H|T]):-
        write(H, " "),
        writelist(T).

Notice how this program uses recursion to process a list. Load the program and try this goal:

    writelist([1, 2, 3, 4]).

2. The next example, Program ch11e02.pro, writes out the elements in a list with no more than five elements per line.

/* Program ch12e02.pro */

    /* Copyright (c) 1986, '95 by Prolog Development Center */

DOMAINS
    integerlist = integer*

PREDICATES
    writelist(integerlist)
    write5(integerlist,integer)

CLAUSES
    writelist(NL):-
        nl,
        write5(NL,0),nl.
    write5(TL,5):-!,
        nl,
        write5(TL, 0).
    write5([H|T],N):-!,
        write(H," "),
        N1=N+1,
        write5(T,N1).
    write5([],_).

If you give the program this goal:

    writelist([2, 4, 6, 8, 10, 12, 14, 16, 18, 20, 22]).

Visual Prolog responds with:

    2 4 6 8 10
    12 14 16 18 20
    22    

3. Frequently, you may want a predicate that displays compound data structures in a more readable form. Program ch11e03.pro displays a compound object like:

        plus(mult(x, number(99)), mult(number(3), x))

in the form:

        x*99+3*x

(This is known as infix notation.)

/* Program ch12e03.pro */

    /* Copyright (c) 1986, '95 by Prolog Development Center */

DOMAINS
    expr = number(integer); x; log(expr);
    plus(expr, expr); mult(expr, expr)

PREDICATES
    writeExp(expr)

CLAUSES
    writeExp(x):-write('x').
    writeExp(number(No)):-write(No).
    writeExp(log(Expr)):-
        write("log("), writeExp(Expr), write(')').
    writeExp(plus(U1, U2)):-
        writeExp(U1),write('+'),writeExp(U2).
    writeExp(mult(U1,U2)):-
        writeExp(U1),write('*'),writeExp(U2).

4. Program ch11e04.pro is similar to Program ch11e03.pro.

/* Program ch12e04.pro */

    /* Copyright (c) 1986, '95 by Prolog Development Center */

DOMAINS
    sentence
   = sentence(nounphrase, verbphrase)
    nounphrase = nounp(article, noun); name(name)
    verbphrase = verb(verb); verbphrase(verb, nounphrase)
    article, noun, name, verb = symbol

PREDICATES
    write_sentence(sentence)
    write_nounphrase(nounphrase)
    write_verbphrase(verbphrase)

CLAUSES
    write_sentence(sentence(S,V)):-
        write_nounphrase(S),write_verbphrase(V).
    write_nounphrase(nounp(A,N)):-
        write(A,' ',N,' ').
    write_nounphrase(name(N)):-write(N,' ').
    write_verbphrase(verb(V)):-write(V,' ').
    write_verbphrase(verbphrase(V,N)):-
        write(V,' '),write_nounphrase(N).

Try Program ch11e04.pro with this goal:

    write_sentence(sentence(name(bill), verb(jumps))).

Exercise

Write a Visual Prolog program that, when given a list of addresses contained in the program as clauses of the form:

    address("Sylvia Dickson", "14 Railway Boulevard","Any Town", 27240).

displays the addresses in a form suitable for mailing labels, such as:

    Sylvia Dickson
    14 Railway Boulevard
    Any Town
    27240

(2) writef/*

The writef predicate allows you to produce formatted output; it uses this format:

    writef(FormatString, Arg1, Arg2, Arg3, ...,ArgN)
                                                                   /* (i, i, i, i, ..., i) */

Arg1 to ArgN must be constants or bound variables belonging to standard domains; it is not possible to format compound domains. The format string contains ordinary characters and format specifiers; ordinary characters are printed without modification, and format specifiers take the following form:

    %-m.pf

The characters in the format specifiers following the % sign are optional and have these meanings:

hyphen (-)

Indicates that the field is to be left-justified (right-justified is the default).

m field

Decimal number specifying a minimum field length.

.p field

Decimal number specifying either the precision of a floating-point number or the maximum number of characters to be printed  from a string.

f field

Specifies formats other than the default format for the given object. For example, the f field can specify that integers should be printed as unsigned or hexadecimal numbers.

Visual Prolog recognizes the following format specifiers in the f field:

f

reals in fixed-decimal notation (such as 123.4 or 0.004321)

e

reals in exponential notation (such as 1.234e2 or 4.321e-3)

g

reals in the shorter format of f or e (this is the default for reals)

d,D

integral domains as a signed decimal number

u,U

integral domains as an unsigned decimal integer

o,O

integral domains as an octal number

x,X

integral domains as a hexadecimal number

c

integral domains as a char

s

as a string (symbols and strings)

R

as a database reference number (ref domain only)

B

as a binary (binary domain only)

P

as a function pointer

The ref domain will be described in chapter 14, and the binary and function pointer domains in chapter 11.

For the integral domain specifiers, an uppercase format letter denotes that the associated object is a long type. If no format letter is given, Visual Prolog will automatically select a suitable format.

Examples of Formatted Output

1. The following example program illustrates the effect of different format specifiers on output formatted with writef.

/* Program ch12e05.pro */

2. Here's another example, showing how you can use writef to format your output.

/* Program ch12e06.pro */

 

CLAUSES

    person("Pete Ashton",20,11111.111).

    person("Marc Spiers",32,33333.333).

    person("Kim Clark",28,66666.666).

 

GOAL

        % Name   is left-justified, at least 15 characters wide

        % Age    is right-justified, 2 characters wide

        % Income is right-justified, 9 characters wide, with 2

        %        decimal places, printed in fixed-decimal notation

    person(N, A, I),

    writef("Name= %-15, Age= %2, Income= $%9.2f ¡¬n",N,A,I),

    fail

    ;

    true.

    This produces the following:

            Name= Pete Ashton    , Age= 20, Income= $  11111.11
            Name= Marc Spiers
    , Age= 32, Income= $  33333.33
            Name= Kim Clark
      , Age= 28, Income= $  66666.67

2. Reading

Visual Prolog includes several standard predicates for reading. The four basic ones are readln for reading whole lines of characters, readchar for reading single characters/keystrokes, readint for reading integers, and readreal for reading floating point numbers. Additionally, readterm will read any term, including compound objects. These predicates can all be redirected to read from files.

Another, more specialized, predicate that belong in the reading category is  file_str for reading a whole text file into a string.

(1) readln/1

readln reads a line of text; it uses this format:

    readln(Line)                                            /* (o) */

The domain for the variable Line will be a string. Before you call readln, the variable Line must be free. readln reads up to 254 characters (plus a carriage return) from the keyboard, up to 64K from other devices. If Esc is pressed during input from the keyboard, readln will fail.

(2) readint/1, readreal/1, and readchar/1

readint reads an integer value, using this format:

    readint(X)                                              /* (o) */

The domain for the variable X must be of integer type, and X must be free prior to the call. readint will read an integer value from the current input device (probably the keyboard) until the Enter key is pressed. If the line read does not correspond to the usual syntax for integers, readint fails and Visual Prolog invokes its backtracking mechanism. If Esc is pressed during input from the keyboard, readint will fail.

readreal does as its name conveys: it reads a real number (as opposed to readint, which reads an integer). readreal uses the following format:

    readreal(X)                                             /* (o) */

The domain for the variable X must be real, and X must be free prior to the call. readreal will read a real value from the current input device until the Enter key is pressed. If the input does not correspond to the usual syntax for a real number, readreal fails. If Esc is pressed during input from the keyboard, readreal will fail.

readchar reads a single character from the current input device, using this format:

    readchar(CharParam)                                     /* (o) */

CharParam must be a free variable before you call readchar and must belong to a domain of char type. If the current input stream is the keyboard, readchar will wait for a single character to be typed before it returns. If Esc is pressed during input from the keyboard, readchar will fail.

(3) readterm/2

readterm reads a compound term and converts it to an object; it takes this format:

    readterm(DomainName, Term)                           /* (i, i) */

You call readterm with two arguments: a domain name and a term. readterm reads a line and converts it to an object of the given domain. If the line does not look like write would have formatted the object, readterm gives an error. The standard predicate readtermerror may be used in connection with a trap to produce customized error handling for readterm. See chapter 11.

readterm is useful for handling terms in text files. For example, you can implement you own version of consult.

(4) file_str/2

file_str reads characters from a file and transfers them to a variable, or creates a file and writes the string into the file. It uses this format:

    file_str(Filename, Text)                     /* (i, o), (i, i) */

If, before your program calls file_str, the variable Text is free, file_str reads the entire contents of the file Filename into Text. In the DOS-related versions of Visual Prolog, an eof character (Ctrl+Z) will terminate reading when encountered and will not be included in the string.

For example, the call

    file_str("t.dat", My_text)

binds My_text to the contents of the file t.dat. The file size can't exceed the maximum length of a string, which is 64 Kbytes on the 16-bit platforms. If the file exceeds the maximum size, file_str will return an error message.

With My_text bound to the text in "t.dat", file_str("t.bak", My_text) will create a file called t.bak that contains the text from "t.dat". If t.bak already exists it will be overwritten.

(5) Examples

These examples demonstrate how you can use the standard reading predicates to handle compound data structures and lists as input.

1. Program ch11e07.pro illustrates assembling of compound objects from individually read pieces of information.

/* Program ch12e07.pro */

 

DOMAINS

    person = p(name, age, telno, job)

    age = integer

    telno, name, job = string

 

PREDICATES

    readperson(person)

    run

 

CLAUSES

    readperson(p(Name,Age,Telno,Job)):-

        write("Which name ? "), readln(Name),

        write("Job ? "), readln(Job),

        write("Age ? "), readint(Age),

        write("Telephone no ? "), readln(Telno).

 

    run :-

        readperson(P),nl,write(P),nl,nl,

        write("Is this compound object OK (y/n)"),

        readchar(Ch),Ch='y', !.

    

    run :-

        nl,write("Alright, try again"),nl,nl,run.

 

GOAL

    run.

2. This next example reads one integer per line until you type a non-integer (such as the X key); then readint  will fail and Visual Prolog displays the list.

/* Program ch12e08.pro */

DOMAINS

    list = integer*

 

PREDICATES

    readlist(list)

 

CLAUSES

    readlist([H|T]):-

        write("> "),

        readint(H),!,

        readlist(T).

    readlist([]).

 

GOAL

        write("*************** Integer List *****************"),nl,

        write(" Type in a column of integers, like this:"),nl,

        write("  integer (press ENTER)¡¬n  integer (press ENTER)¡¬n"),

        write("  etc.¡¬n¡¬n Type X (and press ENTER) to end the list.¡¬n¡¬n"),

        readlist(TheList),nl,

        write("The list is: ",TheList).

Load Program ch12e08.pro and run it. At the prompt, enter a column of integers (such as 1234 Enter 567 Enter 89 Enter 0 Enter), then press X Enter to end the list.

Exercise

Write and test clauses for a predicate readbnumb, which, in the call:

    readbnumb(IntVar)

converts a user-input, 16-bit binary number like "1111 0110 0011 0001" to a corresponding integer value to which IntVar is bound. Check your work by writing a program that contains readbnumb.

3. Binary Block Transfer

Three standard predicates allow reading and writing of binary blocks, or byte sequences of a given length. They all use the binary standard domain. This emulates an array, with a word (dword on the 32-bit versions of Visual Prolog) in front, holding the size. For a complete description of the binary domain, see chapter 11.

(1) readblock/2

readblock has the following format:

    readblock(Length,BTerm)                              /* (i, o) */

where Length is the number of bytes to read and BTerm is the returned binary term. As described in chapter 11, there are no restrictions on the contents of a binary term, and it will contain whatever was read from the file including zeros and DOS eof-markers (Ctrl+Z).

The current input device must be assigned to a file (see readdevice).

If Length = 0 is specified, the readblock attempts to read maximum possible number of bytes from an input device. (Remember that BinBlock < 64 K on 16-bit platforms).

If Length is larger than the actual remaining number of bytes in the file - then the readblock generates the run-time error 1111: "Wrong number of bytes read from file".

(2) writeblock/2

writeblock complements readblock:

    writeblock(Length,BTerm)                             /* (i, i) */

As with readblock, there are no restrictions on the contents of BTerm. The Length specifies how many bytes to write; a length of 0 will write the whole term.

For compatibility with previous versions of Visual Prolog, where binary blocks were disguised as strings, writeblock may be called with a string argument instead of a binary term. In this case, it is imperative that Length contains the correct number of bytes to write.

(3) file_bin/2

file_bin will read a whole file into a binary term, and vice versa. It takes two arguments, the filename and the binary term:

    file_bin(FileName,BinTerm)                    /* (i, o) (i, i) */