CHAPTER 15    System-Level Programming

 

Visual Prolog provides several predicates that allow you to access your PC's operating system and - to the extent that operating system allows - the hardware directly. We summarize those predicates in this chapter, first taking a look at the ones giving access to the OS, then those that perform bit-level logical and shifting operations. After that, we discuss a set of predicates that provide low-level support for manipulating the DOS BIOS, memory, and other hardware elements. We end this chapter with a couple of examples that demonstrate how to use some of these predicates within a Visual Prolog application.

Access to the operating system

With a handful of predicates, you can access the operating system while running the Visual Prolog integrated environment, as well as build the ability to access the run-time computer's operating system right into your Visual Prolog applications. You can execute any external program with a call to system, call the date and time facilities with date and time, investigate the environment table with envsymbol, and read the command-line arguments with comline. Furthermore, you can establish the start-up directory and exe-filename of the program by calling syspath, and the marktime, the timeout and the sleep predicates provide time-tunneling capacity. Then there's the inevitable sound and beep predicates, and finally osversion returning the operating system version, diskspace returning the amount of free disk space, and three versions of storage used to determine memory used.

This section describes each of these predicates in detail and provides some practical examples that demonstrate how to use them.

(1) system/1

Visual Prolog programs provide access to the OS through the system predicate, which takes the following form:

    system("command")                                       /* (i) */

If the argument is an empty string (""), a new command interpreter will be run in interactive mode.

Examples

1. To copy the file B:ORIGINAL.FIL to a file A:NEWCOPY.FIL from within the Visual Prolog system, you could give the goal

        system("").

    then copy the file using the usual command,

        copy b:original.fil newcopy.fil

    You could then return to Visual Prolog by typing

        exit

    after which you are back in your program again.

2. To rename the file (without going out to the OS), you could give the command

        system("ren newcopy.fil newcopy.txt").

(2) system/3

This extended version of the system predicate provides two extra features: one for returning the OS error level, and one for resetting the run-time system's video mode. The latter has no effect in OS/2 or Windows. In UNIX, this argument is used to indicate that the process has no interaction with the terminal, and hence that there's no need to clear and reset it. This is a somewhat unfortunate dual use of the same argument, but it fulfills the typical needs of users.

system/3 takes this format:

    system(CommandString, ResetVideo, ErrorLevel)       /* (i,i,o) */

The error level is returned in ErrorLevel. This is the program return code known by the OS at the time control returns to the program issuing the system call. In DOS and OS/2 this is only available for .COM and .EXE files.

In textmode DOS, ResetVideo controls whether your program should reset the video hardware to the state it was in before system/3 was called. ResetVideo = 1 resets the video mode; ResetVideo = 0 does not. When ResetVideo = 0, your program will run in the new video mode you set, even if that's a mode not specifically supported by Visual Prolog. (For information about setting the run-time system's video mode, refer to the reference manual for the video hardware.)

In other words, if your external program MYSETMD sets the video hardware to a mode not specifically supported by Visual Prolog, and you place the following calls to system in your Visual Prolog program (running from the development environment), you can actually make your program run in that unsupported mode:

    system("mysetmd", 0, ErrorLevel),

Note: The external program must be compatible with the hardware at least at the BIOS level (updating the BIOS variables rows and columns on-screen).

(3) envsymbol/2

The envsymbol predicate searches for environment symbols in the application's environment table; the SET (OS) commands set these symbols.  envsymbol takes this format:

    envsymbol(EnvSymb, Value)                             /* (i,o) */

For example, the command

    SET SYSDIR=C:¡¬FOOL

sets the symbol SYSDIR to the string C:¡¬FOOL, and the goal

    /*...*/
    envsymbol("SYSDIR", SysDir),
    /*...*/

searches the environment for the symbol SYSDIR, binding SetValue to C:¡¬FOOL.

envsymbol will fail if the symbol does not exist.

(4) date and time

Visual Prolog has three more handy OS-related standard predicates: two forms of date and time. The date/3 and time/3 predicates can be used in two ways, depending on whether their parameters are free or bound on entry.

With input flow, time and date will set the internal system clock to the time specified (in UNIX you need root privileges to do this). If all variables are free, the system will bind them to the internal clock's current values.

    time(Hours, Minutes, Seconds, Hundredths)
                            
                                           /* (i,i,i,i), (o,o,o,o) */

Note that the UNIX version of time doesn't return anything useful in the Hundredths argument.

date/3 also relies on the internal system clock and operates similarly to time; it takes the following form:

    date(Year, Month, Day)                                       /* (i,i,i), (o,o,o) */

date/4 only has an output flow version. The fourth argument is the weekday number, but what numbering scheme is used is operating system dependent. However, it's fairly common that 0 is Sunday, 1 is Monday, etc.

    date(Year, Month, Day, WeekDay)                               /* (o,o,o,o) */

Example

Program 2 uses time to display the time elapsed during a listing of the default directory.

/* Program ch15e02.pro */

(5) comline/1

comline reads the command-line parameters used when invoking a program; this is its format:

    comline(CommandLine)                                    /* (o) */

where CommandLine is a string.

(6) syspath/2

syspath returns the start-up directory and name of the program calling it. syspath looks as follows:

    syspath(HomeDir,ExeName)                             /* (o,o) */

The main use for syspath is to provide programs the possibility of loading files from their home directory, as well as constructing helpful command-line error messages: <progname>: Usage: [-foul] <blah> <blah> <blah>.

On UNIX, the start-up directory is not directly available to a program. In order to use syspath on UNIX, an initialization predicate, initsyspath, must be called. In particular, this must be called before the program changes its working directory, if this becomes necessary. If initsyspath isn't called, syspath will exit with an error code of 1138.

1. Timing Services

Visual Prolog provides two different timing services: execution suspension, and elapsed-time testing. Some special notes apply to UNIX, see the description of difftime below.

(1) sleep/1

sleep suspends program execution for a specified length of time. It looks like this

    sleep(CSecs)                                           /* (i) */

where Csecs is the time (in centiseconds, i.e. 1/100ths) to sleep. The exact length of time the program will wait may vary, depending on CPU / OS activity, and you shouldn't expect greater accuracy than 20-50 milliseconds.

In UNIX, sleep uses the nap(S) system call for delays and fractions of delays less than 1 second. This call uses the kernel's callout table, and it may be necessary to increase the size of this (kernel parameter NCALL) to prevent overflows if more than 10-20 processes simultaneously use sleep with fractional delays or nap(S).

(2) marktime/2

marktime returns a time-stamp which may later be tested for expiration using the timeout predicate. marktime has the following format:

    marktime(CSecs,Ticket)                                /* (i,o) */

where CSecs is the required length of time Ticket should last. The Ticket is an implementation-defined structure holding the timing information, currently masquerading as a real number.

(3) timeout/1

timeout tests a time-ticket returned by marktime for expiration. If it has expired, timeout succeeds, otherwise it fails. timeout looks like this:

    timeout(Ticket)                                         /* (i) */

As with sleep, don't expect too fine a granularity.

(4) difftime

On UNIX, the standard predicate time doesn't provide a resolution in 100ths, so any timing calculations will be rather rough. However, the UNIX version of Visual Prolog has a standard predicate difftime:

    difftime(real,real,real)                            /* (i,i,o) */

which returns the difference between the 1st and the 2nd timemark, in hundredths of seconds as a floating-point number. The first timemark should be the younger, and the second the older, i.e. the usage is

    marktime(0,M1), lengthy_process, marktime(0,M2),
    difftime(M2,M1,Diff).

In order for marktime and difftime to work, they must know how many clock-ticks the machine has per second. For UNIX executables, they establish this by calling the sysconf library function (see sysconf(S)), which is a very safe mechanism. However, for XENIX executables they have to call the library function gethz (see gethz(S)), which in it's current implementation simply examines a shell variable called HZ. Thus it is critical that this variable has the correct value, which, unless it's a whole new world when you read this, is 60.  If gethz fails (e.g. because HZ doesn't exist), marktime will exit with error 1136.  The same applies to difftime if either marktime has never been called, or if marktime exited due to failure in gethz.

The granularity of sleep and the marktime and timeout predicates is system-defined, currently being 1/60th of a second. Note that timemarks do not survive reboots. Under UNIX they're the number of machine clock-ticks since "an arbitrary point in the past" which in practice means system start-up. With 60 ticks/second, this also means that the tick count wraps around zero after approx. 2.26 years.

Example

Program 4 below demonstrates marktime and timeout.

/* Program ch15e04.pro */

 

CLAUSES

    ttimeout(TM):-timeout(TM),!.

    ttimeout(TM):-

        write("No timeout, sleep 0.5 secs"),nl,

        sleep(50),

        ttimeout(TM).

 

GOAL

        marktime(400,TM),                                     % 4 secs

        ttimeout(TM),

        write("¡¬nBINGO!¡¬n").

(5) sound/2

sound generates a sound in the PC's speaker:

    sound(Duration,Frequency)                             /* (i,i) */

where Duration is the time in 1/100ths of a second.

On UNIX, sound works only on the ANSI console; whether you're running on this is established by examining the TERM shell variable. On other terminals, sound is equivalent to beep.

(6) beep/0

    beep                                         /* (no arguments) */

In the DOS-related versions of Visual Prolog, beep is equivalent to sound(50,1000).

On UNIX, beep writes the bell character to the file used for terminal output. If the program is in terminal mode, all buffering will be bypassed.

(7) osversion/1

osversion returns the current operating system version and looks like this:

    osversion(VerString)                                    /* (o) */

The format for VerString is operating system defined. For DOS and OS/2, it consists of the major and minor version numbers, separated by a dot (full stop), e.g. "3.30". Note that the major version number currently returned by OS/2 is 10, rather than 1. In UNIX, the string contains the information returned by uname(S).

(8) diskspace/2

diskspace returns as an unsigned long the available disk space, using the following format:

    diskspace(Where,Space)                                /* (i,o) */

The space is reported in bytes.

In the DOS-related versions of Visual Prolog, Where should be a character specifying the drive letter. In the UNIX version, it should be the name of a file residing on the file system you want to query (see statfs(S)). You may use simply "/" for the root file system, or an empty or null string in which case information is retrieved for the file system holding the current working directory. The space reported will be the smaller of the actual space and the ulimit for the process (see ulimit(S)).

(9) storage/3

The standard predicate storage returns information about the three run-time memory areas used by the system (stack, heap, and trail, respectively) as unsigned longs:

    storage(StackSize,HeapSize,TrailSize)               /* (o,o,o) */

The values are all in bytes.

In all versions of Visual Prolog, TrailSize contains the amount of memory used by the trail.

In the DOS-related versions, StackSize indicates how much stack space is left. In UNIX, StackSize is the exact opposite, namely how much stack that's been used so far.

Finally, the HeapSize shows how much memory is available to the process.

In UNIX this is the difference between the current break value and the maximum possible break value (see ulimit(S) and brk(S)), which again is set by the kernel parameter MAXUMEM. It does not include memory held in freelists in the heap.

In DOS, the HeapSize is the unallocated physical memory between the top of the GStack and the bottom of the heap. It does not include memory held in freelists in the heap. The storage predicate returns the size that you can be sure of having when you're loading a file or going out to the operating system.

In OS/2 the storage will be limited by the virtual memory which is limited by the size of the disk where the swap file resides. Since there is no easy way to find where the swap file resides, the storage predicate will for the heap just return the size of the largest block OS/2 can allocate without compacting and/or swapping memory. You can't really use that for anything, but it gives you an indication of memory fragmentation. If you feel certain that you know where the swap file resides, you can use the diskspace standard predicate to check the free space available.

(10) storage/0

The 0-arity version of storage is primarily intended for debugging purposes. It prints in the current window an overview of the amount of memory in use by the different parts of Visual Prolog's memory management, as well as the number of backtrack points.