Examples

 

1. List Handling

In this section we give a more useful example that shows how to convert a list to an array and back to a list again.

The C routine ListToArray takes a list of integers, converts this to an array placed on the Global Stack, and returns the number of elements. The conversion is done in three steps:

The C routine ArrayToList takes an integer array and the size of the array as arguments, then converts these to a list of integers. This routine only makes one pass, building the list as it indexes through the array.

All of this is used in the C-coded predicate inclist. When given a list of integers, inclist first converts the input list to an array, increments the elements of the array by 1, then converts the array back to a list of integers.

/* Program lstar_p.pro */

project "lstar"

global domains
    ilist = integer*

global predicates
    inclist(ilist,ilist) - (i,o) language c

goal
    inclist([1,2,3,4,5,6,7],L), write(L).

Here is the C program defining the two C procedures ListToArray and ArrayToList, and the external Visual Prolog predicate inclist.

/* Program lstar_c.c */

 

void *MEM_AllocGStack(unsigned);

 

typedef struct ilist {

    BYTE Functor;

    int Value;

    struct ilist *Next;

} INTLIST;

 

int ListToArray(INTLIST *List,int **ResultArray)

{

    INTLIST *SaveList = List;

    int *Array, len;

    register int *ArrP;

    register int i;

 

/* Count the number of elements in the list */

    i = 0;

    while ( List->Functor == listfno ) {

        i++;

        List = List->Next;

    }

    len = i;

 

Array = MEM_AllocGStack(i*sizeof(int));

    ArrP = Array;

 

/* Transfer the elements from the list to the array */

    List = SaveList;

    while ( i != 0 ) {

        *ArrP++ = List->Value;

        List = List->Next;

        i--;

    }

        *ResultArray = Array;

        return(len);

    }

 

void ArrayToList(register int *ArrP,register int n,
    register INTLIST **ListPP)

    {

        while ( n != 0 ) {

            *ListPP = MEM_AllocGStack(sizeof(INTLIST));

            (*ListPP)->Functor = listfno;

            (*ListPP)->Value = *ArrP++;

            ListPP = &(*ListPP)->Next;

            n--;

    }

    *ListPP = MEM_AllocGStack(sizeof((*ListPP)->Functor));
                                                                                 /* End of list */

    (*ListPP)->Functor = nilfno;

}

void inclist(INTLIST *InList,INTLIST **OutList)

{

    register int *ArrP, i, len;

    int *Array;

 

    len = ListToArray(InList,&Array);

    ArrP = Array;

    for ( i = 0; i < len; i++)

        ++*ArrP++;

    ArrayToList(Array,len,OutList);

}

This program belongs to the kind where memory alignment can be critical. If you intend to compile to several platforms, you're well advised to keep an eye on this. As a first step, check that the sizes of the structures shared by C and Prolog are the same; the padding applied when aligning on non-byte boundaries will make things a bit bigger. The sizeof function comes in handy here. You can write a small C function:

    unsigned c_ilsize(void)
    {
    return(sizeof(INTLIST));
    }

returning the size of the INTLIST structure. This can then be used by a Prolog predicate to verify that the sizes of INTLIST and ilist are identical:

GLOBAL PREDICATES
    unsigned c_ilsize() language C

PREDICATES
    scheck

CLAUSES
    scheck:- ILSize = sizeof(ilist), ILSize = c_ilsize(), !.
    scheck
:- write("ilist element sizes differ¡¬n"), exit(1).

2. Calling Prolog from Foreign Languages

If you supply Prolog clauses for global predicates declared as being of foreign language, those predicates may be called from foreign languages. They will have parameter access and entry and exit code, including register preservation, as for the language specified.

(1) Hello

This small project is hello-world, with a twist.

/* Program hello_p.pro */

global predicates
    char prowin_msg(string) - (i) language c
    hello_c - language c

clauses
    prowin_msg(S,C) :-
        write(S," (press any key)"), readchar(C).

goal
        prowin_msg("Hello from PDC Prolog"),
        hello_c.

The global predicate prowin_msg is now accessible from C and can be called just like any other C function:

/* Program hello_c.c */

    char prowin_msg(char *);

    void hello_c()
    {
        while ( prowin_msg("Hello from C (press 'C')") != 'C' )
        ;
    }

As is evident, values may be returned to foreign languages.

(2) Standard Predicates

Most of Visual Prolog's standard predicates can be called from C, but their public names and exact functionality are subject to change without notice. It's therefore strongly recommended that you write a small set of interface routines if you want to call Visual Prolog standard predicates from C. The following illustrates bindings to a number of Visual Prolog's DOS Textmode I/O predicates:

/* Program spred_p.pro */

project "spred"

global predicates

mymakewindow(integer,integer,integer,string,integer,integer,
                     integer,integer)

 

extprog language c

 

clauses

 

mymakewindow(Wno, Wattr, Fattr, Text, Srow, Scol, Rows, Cols):-

    makewindow(Wno, Wattr, Fattr, Text, Srow, Scol, Rows, Cols).

myshiftwindow(WNO):- shiftwindow(WNO).

 

myremovewindow:- removewindow.

 

write_integer(I):- write(I).

 

write_real(R):- write(R).

 

write_string(S):- write(S).

 

myreadchar(CH):- readchar(CH).

 

myreadline(S):- readln(S).

 

goal

These may be accessed freely by C, as illustrated by extprog:

/* Program spred_c.c */

void extprog(void)

makewindow(1,7,7,"Hello there",5,5,15,60);

write_string("¡¬n¡¬nIsn't it easy");

readchar(&dummychar);

write_string("¡¬nEnter your name: ");

readline(&Name);

write_string("¡¬nYour name is: ");

write_string(Name);

readchar(&dummychar);

removewindow();

}

3. Calling an Assembler Routine from Visual Prolog

You can also call assembler routines from Visual Prolog. The activation record is the same as for pascal (that is, parameters are pushed left to right), and the called routine should pop the stack itself. If you have a C compiler supporting inline assembler, things will be considerably easier than if you have to do everything yourself.

In any case there seems to be little point in using assembler since C handles most things, but a small example is included here for completeness. For obvious reasons, the code differs between 16 and 32 bit platforms.

Suppose you want to write a routine returning a 32-bit sum of the characters in a string, and also verifies that all characters are within a certain range, say A-Z.

The Prolog code for this could be:

/* Program csum_p.pro */

project "csum"

 

global predicates

predicates

clauses

goal

where we have adopted the convention that a return value of 0 means the string was OK.

Here is the suitable 16-bit assembler code:

/* Program csum_a16.asm */

 

; 16-bit version

 

CSUM_A16_TEXT     SEGMENT  WORD PUBLIC 'CODE'

CSUM_A16_TEXT     ENDS

_DATA                   SEGMENT  WORD PUBLIC 'DATA'

_DATA                   ENDS

CONST                  SEGMENT  WORD PUBLIC 'CONST'

CONST                  ENDS

_BSS                     SEGMENT  WORD PUBLIC 'BSS'

_BSS                     ENDS

DGROUP                GROUP   CONST, _BSS, _DATA

                            ASSUME  CS: CSUM_A16_TEXT, DS: DGROUP, SS: DGROUP

 

CSUM_A16_TEXT         SEGMENT

    ASSUME                CS: CSUM_A16_TEXT

 

PUBLIC                   sum_verify

sum_verify               PROC FAR

    push                   bp

    ov                      bp,sp    

 

lolim equ 16

hilim equ 14

string equ 10

sum equ 6

    xor        dx,dx

    xor        bx,bx                              ; Do sum in dx:bx

    les        di,[bp+string]                    ; Pointer to string

    mov       cl,byte ptr [bp+lolim]             ; Low limit in cl

    mov       ch,byte ptr [bp+hilim]           ; High limit in ch

    xor        ax,ax

 

ALIGN 2

loopy:

    add        bx,ax                                     ; Add sum

    adc        dx,0

    mov       al,byte ptr es:[di]

    inc         di

    cmp       al,cl

    jb          end_check

    cmp       al,ch

    jbe         loopy

 

end_check:

    or         al,al

    jnz        go_home

    les        di,[bp+sum]

    mov      es:[di],bx

    mov      es:[di+2],dx

    inc        ax; ax: 0 -> 1

 

go_home:

    dec        ax                         ; ax: 1 -> 0, or 0 -> -1

    mov       sp,bp

    pop        bp

    ret         12

sum_verify   ENDP

 

CSUM_A16_TEXT ENDS

END

When writing assembler code, take special care that the sizes of things on the stack follow the machine's natural word-size. This is 2 bytes on 16-bit machines and 4 bytes on 32-bit machines. A good first attempt is to compile a dummy C routine, with the correct parameters and local variables, to assembler, and then use the entry, exit, and variable access code generated by the C compiler.

It isn't necessary to preserve any of the usual registers when foreign language routines are called from Prolog, but if you're calling from C or assembler it's assumed that you preserve si and di (esi and edi on 32-bit platforms). On 32-bit platforms, ebx must also be preserved.

Summary

 

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

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

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

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

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

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