Visual Prolog's File System

In this section, we give you a look at Visual Prolog's file system and the standard predicates relevant to files. We also introduce I/O redirection, an efficient method for routing input and output to various devices. With a few exceptions, the file system works identically in the different versions of Visual Prolog.

Visual Prolog uses a current_read_device, from which it reads input, and a current_write_device, to which it sends output. Normally, the keyboard is the current read device, and the screen is the current write device. However, you can specify other devices. For instance, input could be read from an externally stored file (on disk perhaps). Not only can you specify other devices, you can even reassign the current input and output devices while a program is running.

Regardless of what read and write devices you use, reading and writing are handled identically within a Visual Prolog program. To access a file, you must first open it. A file can be opened in one of four ways:

for reading

for writing

for appending

for modification

A file opened for any activity other than reading must be closed when that activity is finished, or the changes to the file might be lost. You can open several files simultaneously, and input and output can be quickly redirected between open files. In contrast, it takes much longer to open and close a file than to redirect data between files.

When Visual Prolog opens a file, it connects a symbolic name to the actual file name. Visual Prolog uses this symbolic name when directing input and output. Symbolic file names must start with a lower-case letter and must be declared in the file domain declaration like this:

    file = file1; source; auxiliary; somethingelse

Only one file domain is allowed in any program. Visual Prolog recognizes five predefined file alternatives:

keyboard

reading from the keyboard (default)

screen

writing to the screen

stdin

reading from standard input

stdout

writing to standard output

stderr

writing to standard error

These predefined alternatives must not appear in the file domain declaration; they don't need to be opened and they should not be closed. Note, that when using the VPI strategy, only the screen alternative can be used.

1. Opening and Closing Files

The following sections describe the standard predicates for opening and closing files.

Note: In the DOS-related versions of Visual Prolog, remember that the backslash character, used to separate subdirectories, is an escape character. You must always use two backslash characters when you give a path in the program; for example, the string

    "c:¡¬¡¬prolog¡¬¡¬include¡¬¡¬iodecl.con"

represents the path name

    c:¡¬prolog¡¬include¡¬iodecl.con

(1) openread/2

openread opens the file OSFileName for reading, using this format:

    openread(SymbolicFileName, OSFileName)               /* (i, i) */

Visual Prolog refers to the opened file by the symbolic name SymbolicFileName declared in the file domain. If the file can't be opened, Visual Prolog returns an error message.

(2) openwrite/2

openwrite opens the file OSFileName for writing; it takes this format:

    openwrite(SymbolicFileName, OSFileName)               /* (i,i) */

If the file already exists, it is erased. Otherwise, Visual Prolog creates a new file and makes an entry in the appropriate directory. If the file can't be created, the predicate exits with an error message.

(3) openappend/2

openappend opens the file OSFileName for writing at the end, using this format:

    openappend(SymbolicFileName, OSFileName)             /* (i, i) */

If the file can't be opened for write access, Visual Prolog issues an error message.

(4) openmodify/2

openmodify opens the file OSFileName for both reading and writing; if the file already exists, it won't be overwritten. openmodify takes this format:

    openmodify(SymbolicFileName, OSFileName)             /* (i, i) */

If the system can't open OSFileName, it issues an error message. openmodify can be used in conjunction with the filepos standard predicate to update a random-access file.

(5) filemode/2

When a file has been opened, filemode sets the specified file to text mode or binary mode, using this format:

    filemode(SymbolicFileName, FileMode)                 /* (i, i) */

If FileMode = 0, the file specified by SymbolicFileName is set to binary mode; if FileMode = 1, it's set to text mode.

In text mode, newlines are expanded to carriage- return/line-feed pairs during writes, and carriage-return/line-feed pairs are converted to newlines during reads.

Carriage return    = ASCII 13
Line feed
            = ASCII 10

In binary mode, no expansions or conversions occur. To read a binary file, you can only use readchar or the binary file-access predicates discussed in chapter 11.

filemode is only relevant in the DOS-related versions of Visual Prolog. In the UNIX version it has no effect.

Don't confuse filemode with the peculiarly named DosQFileMode and DosSetFileMode OS/2 primitives - they get or change the attributes of physical disk files.

(6) closefile/1

closefile closes the indicated file; it takes this format:

    closefile(SymbolicFileName)                             /* (i) */

This predicate always succeeds, even if the file has not been opened.

(7) readdevice/1

readdevice either reassigns the current_read_device or gets its name; the predicate takes this format:

    readdevice(SymbolicFileName)                       /* (i), (o) */

readdevice reassigns the current read device if SymbolicFileName is bound and has been opened for reading. If SymbolicFileName is free, readdevice binds it to the name of the current active read device.

(8) writedevice/1

writedevice either reassigns or gets the name of the current_write_device; it takes this format:

    writedevice(SymbolicFileName)                      /* (i), (o) */

writedevice reassigns the current write device if the indicated file has been opened for either writing or appending. If SymbolicFileName is free, writedevice binds it to the name of the current active write device.

Examples

1. The following sequence opens the file mydata.fil for writing, then directs all output produced by clauses between the two occurrences of writedevice to that file. The file is associated with the symbolic file name destination appearing in the declaration of the file domain.

GOAL

    openwrite(destination, "mydata.fil"),

    writedevice(OldOut),          /* gets current output device */

    writedevice(destination),   /* redirects output to the file */

    :

    :

    writedevice(OldOut),                /* resets output device */

2. Program ch11e09.pro uses some standard read and write predicates to construct a program that stores characters typed at the keyboard in the file tryfile.one. Characters typed are not echoed to the display; it would be a good exercise for you to change the program so that characters are echoed. The file is closed when you press the # key.

/* Program ch12e09.pro */

DOMAINS

    file = myfile

 

PREDICATES

    readloop

 

CLAUSES

    readloop:-

        readchar(X),

        X<>'#',!,

        write(X),

        readloop.

    readloop.

 

GOAL

        write("This program reads your input and writes it to"),nl,

        write("tryfile.one. For stop press #"),nl,

        openwrite(myfile,"tryfile.one"),

        writedevice(myfile),

        readloop,

        closefile(myfile),

        writedevice(screen),

        write("Your input has been transferred to the file tryfile.one"),nl.

2. Redirecting Standard I/O

The file domain has three additional options: stdin, stdout, and stderr. The advantage of these file streams is that you can redirect I/O at the command line.

stdin

Standard input is a read-only file; the keyboard, by default. readdevice(stdin) directs the input device to stdin.

stdout

Standard output is a write-only file that defaults to the screen. writedevice(stdout) directs the output device to stdout.

stderr

Standard error is a write-only file that defaults to the screen. writedevice(stderr) directs the output device to stderr.

3. Working with Files

In this section, we describe several other predicates used for working with files; these are filepos, eof, flush, existfile, searchfile, deletefile, renamefile, disk, and copyfile.

(1) filepos/3

filepos can control the position where reading or writing takes place; it takes the form

    filepos(SymbolicFileName, FilePosition, Mode) % (i, i, i), (i, o, i)

With FilePosition bound, this predicate can change the read and write position for the file identified by SymbolicFileName. It can return the current file position if called with FilePosition free. FilePosition is a long value.

Mode is an integer and specifies how the value of FilePosition is to be interpreted, as shown in Table 12.1.

Table 12.1: Mode and FilePosition

Mode

FilePosition

0

Relative to the beginning of the file.

1

Relative to current position.

2

Relative to the end of the file. (The end of the file is position 0.)

When returning FilePosition, filepos will return the position relative to the beginning of the file irrespective of the value of Mode. Note: In the DOS-related versions of Visual Prolog, filepos does not consider files in text mode to be different from files in binary mode. No translation of DOS newline conventions takes place, and a newline in a file following DOS newline conventions consists of two characters.

Example

1. The following sequence writes the value of Text into the file somefile.pro (referred to by Prolog as myfile), starting at position 100 (relative to the beginning of the file).

2. Using filepos, you can inspect the contents of a file on a byte-by-byte basis, as outlined in Program ch11e10.pro. This program requests a file name, then displays the contents of positions in the file as their position numbers are entered at the keyboard.

/* Program ch12e10.pro */

 

DOMAINS

    file = input

 

PREDICATES

    inspect_positions(file)

 

CLAUSES

    inspect_positions(UserInput):-

        readdevice(UserInput),

        nl,write("Position No? "),

        readln(X),

        term_str(ulong,Posn,X),

        readdevice(input),

        filepos(input,Posn,0),

        readchar(Y),nl,

        write("Char is: ",Y),

        inspect_positions(UserInput).

 

GOAL

        write("Which file do you want to work with ?"),nl,

        readln(FileName),

        openread(input, FileName),

        readdevice(UserInput),

        inspect_positions(UserInput).

(2) eof/1

eof checks whether the file position is at the end of the file, in which case eof succeeds; otherwise, it fails. eof has the form

    eof(SymbolicFileName)                                   /* (i) */

eof gives a run-time error if the file has been opened with write-only access. Note that it doesn't consider a DOS eof character (Ctrl+Z) to have any particular meaning.

Example

eof can be used to define a predicate repfile that's handy when operating with files. repfile generates backtrack points as long as the end of the file has not been reached.

The following program converts one file to another where all the characters are upper-case.

/* Program ch12e11.pro */

DOMAINS

    file = input; output

    

PREDICATES

    convert_file

    nondeterm repfile(FILE)

 

CLAUSES

    convert_file :-

        repfile(input),

        readln(Ln),

        upper_lower(LnInUpper,Ln), /* converts the string to uppercase */

        write(LnInUpper),nl,

        fail.

    convert_file.

 

    repfile(_).

    repfile(F):-

        not(eof(F)),

        repfile(F).

 

GOAL

        write("Which file do you want convert ?"),

        readln(InputFileName),nl,

        write("What is the name of the output file ?"),

        readln(OutputFileName),nl,

        openread(input, InputFileName),

        readdevice(input),

        openwrite(output, OutputFileName),

        writedevice(output),

        convert_file,

        closefile(input),

        closefile(output).

(3) flush/1

flush forces the contents of the internal buffer to be written to the named file. It takes this format:

    flush(SymbolicFileName)                                 /* (i) */

flush also requests the operating system to flush its buffers. For versions of DOS previous to 3.30, this entails closing and re-opening the file. For newer versions of DOS, as well as the other platforms, the appropriate operating system function is called.

(4) existfile/1

existfile succeeds if OSFileName exists. It takes this format:

    existfile(OSFileName)                                   /* (i) */

where OSFileName may contain a directory path and the name itself may contain wildcards, e.g. c:¡¬psys¡¬*.cfg. existfile fails if the name does not appear in the directory. However, note that although existfile finds all files, including those with the 'system' and 'hidden' attribute set, it doesn't find directories. This may be accomplished using the directory search predicates described later on.

You can use the following sequence to verify that a file exists before attempting to open it.

    open(File, Name) :-
        existfile(Name), !,
        openread(File, Name).
    open(_, Name) :-
        write("Error: the file ", Name," is not found").

(5) existfile/2

In UNIX, existfile is also available in a two- arity version:

    existfile(OSFileName,AccessMode)                     /* (i, i) */

with AccessMode specifying the type of access desired. This should be one of the following constants:

f_ok to test for existence

x_ok to test for execute permission

w_ok to test for write permission

r_ok to test for read permission

These constants are declared in the include file iodecl.con.

existfile with only one argument tests for file-existence only.

(6) searchfile/3

searchfile is used to locate a file along a path list, and is a kind of automated existfile. It takes three arguments, as follows:

    searchfile(PathList,Name,FoundName)                 /* (i,i,o) */

The PathList is a string containing one or more paths, separated by semicolons (or colons, for UNIX), and Name is the name of the file to locate. If found, FoundName will be bound to the fully qualified name, otherwise searchfile will fail. For instance, for DOS

    SearchFile(".;..;C:¡¬¡¬","autoexec.bat",FoundName),

will - provided autoexec.bat is located in the root of drive C - set FoundName to C:¡¬AUTOEXEC.BAT.

The file name may contain wildcards. In that case, FoundName is bound to the fully qualified wildcard name, which may subsequently be used as input to the directory matching predicates described later on. For instance, if the name is specified as *.bat instead of autoexec.bat in the above example, FoundName will be bound to C:¡¬*.BAT.

(7) deletefile/1

deletefile removes the file specified by its argument:

    deletefile(OSFileName)                                  /* (i) */

deletefile gives an error if it can't remove the file. The OSFileName can not contain wildcards.

(8) renamefile/1

renamefile renames the file OldOSFileName to NewOSFileName. It takes this format:

    renamefile(OldOSFileName, NewOSFileName)             /* (i, i) */

renamefile succeeds if a file called NewOSFileName doesn't already exist and both names are valid file names; otherwise, it gives an error.

(9) disk/1

disk is used to change the current disk and/or directory; it takes this format:

    disk(Path)                                         /* (i) (o) */

Called with a free variable, disk will return the current directory. In the DOS-related versions, to change to another disk without changing the existing current directory on that disk, use D:. where D is the drive letter.

(10) copyfile/2

copyfile is used to copy a file. It takes two file names as follows:

    copyfile(SourceName,DestinationName)                   /* (i,i)*/

The names may be partly or fully qualified file names, including disks and directories. However, no wildcards are allowed. The copied file will have the same attributes (and permissions) as those of the source.

4. File Attributes

Although the standard file open predicates described previously cover all general cases, there may be a need to open or create files with specialized attributes and non-obvious sharing modes. To this end Visual Prolog incorporates a general purpose open predicate, but before discussing that we need to look at file attributes and sharing modes.

The attributes and access modes used by Visual Prolog use the same values as your operating system, with the exception of the default ('normal') attribute in the NonUNIX-related versions of Visual Prolog. However, for easy porting to other environments, you should avoid coding inherently non-portable constructs such as file attributes (and even the fact that files have attributes) all over an application. Rather, wrap things up nicely and write your own intermediate level of predicates, getting and setting information in transparent ways.

The attributes and sharing modes are found in the include file IODECL.CON.

(1) Opening and creating files

When opening or creating a file, the OS needs to know the file's attributes (e.g. 'hidden'), the type of use or access (e.g. 'read'), and how the file may be shared with other programs while open (e.g. 'deny write'). Don't confuse these - they are three different pieces of information, only partly related:

Attributes

The file attributes are the permanent attributes relating to the physical file on disk, whether currently in use by a program or not. In DOS and OS/2 there's only a few attributes, such as 'read only' and 'hidden'. These attributes inform the operating system about how it may handle the file. Network and multiuser operating systems, such as UNIX, typically have a much wider range of attributes. These may include access allowed by other users (e.g. 'execute-only', no read or write, giving copy-protection) and direct instructions to the OS ('this is an executable program').

The attributes have no effect when opening an existing file, as files are unique based on names only. They only apply when creating a new file.

The standard predicates described in the previous section all reference 'normal' files. However, when a file has been modified the archive bit will automatically be set by the operating system when the file is closed.

Access Modes

The access modes indicate how the file will be used. The OS will combine this information with the files physical attributes, to determine if the access requested is acceptable. For instance, opening a file having the read-only physical attribute set, with either fm_access_wo or fm_access_rw will not be accepted.

Sharing Modes

The sharing modes indicate how this process views sharing with other processes. The OS will combine the sharing and access modes with the sharing and access modes specified by other processes, if the file is already in use, to determine if the open call should succeed. If successful, the modes will restrict future open attempts.

Note that conceptually the sharing and access modes work both ways to form a combined set of restrictions on the file: they specify both what the process wants from a file and what it will allow from other processes. For instance, if a file has been opened with 'deny write' and 'read only', an open attempt with 'deny none' and 'write only' will fail because the first process has specified 'deny write' - in this case it is the existing restriction on the file that rejects the open attempt. On the other hand, an open attempt with 'deny read' and 'read only' will fail because the file is already open with read access - in this case it is the current requirement that rejects the open attempt.

Note that the fm_sh_denyrw denies all modes from other processes; it doesn't mean 'deny read- write, but allow read-only or write-only'.

All the standard predicates described in the previous section specify the sharing mode as 'deny write'.

(2) Special File Modes for OS/2, DOS >= 4.0 and UNIX

OS/2 and DOS versions greater than or equal to 4.0, have a special fm_returnerr mode:

The fm_returnerr specify that "media" errors occurring after the file has been opened should return an error to the program, rather than be reported  through a pop-up window. Media errors are those indicating a malfunction of the device, e.g. if writing to a floppy and the drive door is opened - this generates the well-known 'Drive not ready' error. The standard predicates described in the previous section do not specify fm_returnerr, so media errors will generate a pop-up through OS/2's critical error handler.

UNIX, OS/2 and DOS >= 4.0 also have a write- through mode:

The fm_writethru specifies that no write buffering should take place. In this case, every single byte written to the file cause both the physical disk image and the directory entry to be updated, giving a secure file. However, disk writes performed with write-through are excessively slow compared to ordinary writes.

(3) openfile/5

With the general-purpose openfile predicate, files may be created or opened in nonstandard ways. openfile looks like this:

    openfile(SymbolicName,OSName,OpenMode,Attributes,Creation)
                                                /* (i,i,i,i,i) */

The SymbolicName and OSName are the same as for the previously described standard predicates. The rest of the arguments are as follows (please refer to the section on File Attributes a few pages back):

OpenMode is the access and sharing modes for the file. It is formed by adding together one of the fm_access_XX values, one of the fm_sh_XXXXXX and optionally fm_returnerr and fm_writethru. If no access mode is specified, it will be set to 'read only'. If no sharing mode is specified, it will be set to 'deny write'.

Attributes are the attributes for the physical disk file. Valid attributes on DOS and OS/2 are fa_rdonly, fa_hidden, fa_system, fa_arch and fa_normal. If nothing (0) is specified, the attributes will be set to fa_normal. The system and the hidden attributes both have the same effect, namely to hide the file when a 'dir' command is executed. Note that DOS and OS/2 automatically set the archive attribute when an updated file is closed.  For UNIX, the attributes correspond to the file's permissions.

Creation specifies how the presence or absence of an existing file with the same name is to be handled. It is formed by adding  at most one from the cr_ex_XX group and at most one from the cr_noex_XX group. Pay attention to Creation defaults - if nothing (0) is specified. Note that this is the equivalent of specifying cr_ex_fail and cr_noex_fail, i.e. fail if it exists and fail if it doesn't exist. But remember that the actual default Creation action will be set according to the access mode as follows:

fm_access_ro   ->   cr_ex_open + cr_noex_fail 
fm_access_wo   ->   cr_ex_replace + cr_noex_create
fm_access_rw
   ->   cr_ex_open + cr_noex_create

A sensible Creation default for read-write access is a bit tricky: If read-write is specified because the file is opened for 'modification', an existing file of the same name should be opened, not replaced. This is therefore the default. However, if read-write is specified because one wants bidirectional access to a new file, an existing file of the same name should be deleted. This is possible with a call to openfile as follows:

:
FMode = fm_access_rw + fm_sh_denywr + fm_returnerr,
FCrea = cr_ex_replace + cr_noex_create,
openfile(dbfile,"salient.dba",FMode,fa_normal,FCrea),
: