Type Conversion

In this section, we summarize the standard predicates available for type conversion. The predicates are char_int, str_char, str_int, str_real, upper_lower, and finally term_str which converts between terms of any kind and strings.

(1) char_int/2

char_int converts a character into an integer or an integer into a character; it takes this format:

    char_int(Char, Integer)                 /* (i,o), (o,i), (i,i) */

With both its arguments bound, char_int tests that the arguments correspond. With one argument bound and the other free, char_int performs the conversion and binds the output argument to the converted form of the input one.

Note: This predicate is really not needed in newer versions of Visual Prolog because there is automatic conversion between characters and integers. We've left char_int in to be compatible with older versions.

(2) str_char/2

str_char converts a string containing one and only one character into a character, or converts a single character into a string of one character; it takes this format:

    str_char(String, Char)                 /* (i,o), (o,i), (i,i) */]

In the (i,i) flow variant, str_char succeeds if String is bound to the single-character string equivalent of Char. If the length of the string is not 1, str_char fails.

(3) str_int/2

str_int converts a string containing an integer into an integer, or converts an integer into its textual representation; it takes this format:

    str_int(String, Integer)               /* (i,o), (o,i), (i,i) */]

In the (i,i) flow variant, str_int succeeds if Integer is bound to the integer equivalent of the integer represented by String.

(4) str_real/2

str_real converts a string containing a real number into a real number, or converts a real number into a string; it takes this format:

    str_real(String, Real)                 /* (i,o), (o,i), (i,i) */]

In the (i,i) flow variant, str_real succeeds if Real is bound to the real equivalent of the real number represented by String.

(5) upper_lower/2

upper_lower converts an upper-case (or mixed) string or character to all lower-case, or a lower-case (or mixed) string or character to all upper-case; it takes this format:

    upper_lower(Upper, Lower)              /* (i,o), (o,i), (i,i) */]

With both its arguments bound, upper_lower succeeds if Upper and Lower are bound to strings that--except for the case of the letters--are identical; for instance, the goal:

    Str1=samPLEstrING,
    Str2=sAMpleSTRing,
    upper_lower(Str1, Str2)}
    succeeds. Otherwise, it fails.

(6) term_str/3

term_str is a general-purpose conversion predicate and will convert between terms of a specified domain and their string representations. It looks like this:

    term_str(Domain,Term,String)               /* (i,i,o),(i,_,i) */]

where Domain specifies which domain the term belongs to. term_str could replace the various str_* predicates above, for instance, str_real could be implemented as str_real(S,R):- term_str(real,R,S). However, term_str is a somewhat heavier mechanism.

The Domain need not be one of the standard domains, it can be any user-defined domain:

/* Program ch13e04.pro */

 

GOAL

    write("Input list (example [66,73,76,83]): "),

    readln(L),nl,

    str_len(L,Len),

    write("The stringlength of ",L),

    write(" is ",Len,'ˇ¬n').

(7) Examples

This example defines the predicate scanner, which transforms a string into a list of tokens. Tokens are classified by associating a functor with each token. This example uses the predicates isname, str_int, and str_len to determine the nature of the tokens returned by fronttoken.

/* Program ch13e05.pro */

 

DOMAINS

    tok  = numb(integer); name(string); char(char)

    toklist = tok*

 

PREDICATES

    nondeterm scanner(string, toklist)

    nondeterm maketok(string, tok)

 

CLAUSES

    scanner("",[]).

    scanner(Str,[Tok|Rest]):-

        fronttoken(Str, Sym, Str1), maketok(Sym, Tok), scanner(Str1, Rest).

 

    maketok(S,name(S)):-isname(S).

    maketok(S,numb(N)):-str_int(S,N).

    maketok(S,char(C)):-str_char(S, C).

 

GOAL

    write("Enter some text:"),nl,

    readln(Text),nl,

    scanner(Text,T_List),

    write(T_List).

Conversions between the domain types symbol and string, and between char, integer, and real, are handled automatically when using standard predicates and during evaluation of arithmetic expressions. Reals will be rounded during automatic conversions. Visual Prolog performs this automatic conversion as necessary when a predicate is called, as in the following example:

    PREDICATES
        p(integer)

    CLAUSES
        p(X):- write("The integer value is ",X,'ˇ¬n').

With this example, the following goals have the same effect:

    X=97.234, p(X).
    X=97, p(X).
    X='a', p(X).

The following very simple English parser is a practical example of string parsing. This example directly parses strings; if the parser were to be extended, the string should be tokenized using a scanner similar to the one used in Program 4. Whether you're parsing tokens or strings, the algorithm in this program is a good example of how to start.

If you are interested in English-language parsing, we recommend that you take a look at the Sentence Analyzer and Geobase programs in the VPIˇ¬PROGRAMS subdirectory.

/* Program ch13e06.pro */

 

    verb_phrase = verb(verb) ; verb_phrase(verb,noun_phrase)

    verb        = string

 

    detrm       = string

 

PREDICATES

    nondeterm s_sentence(string,sentence)

    nondeterm s_noun_phrase(string,string,noun_phrase)

    nondeterm s_verb_phrase(string,verb_phrase)

    d(string)

    n(string)

    v(string)

 

CLAUSES

    s_sentence(Str,s(N_Phrase,V_Phrase)):-

        s_noun_phrase(Str, Rest, N_Phrase),

        s_verb_phrase(Rest, V_Phrase).

 

    s_noun_phrase(Str,Rest,noun_phrase(Detr,Noun)):-

        fronttoken(Str,Detr,Rest1),

        d(Detr),

        fronttoken(Rest1,Noun,Rest),

        n(Noun).

 

    s_noun_phrase(Str,Rest,noun(Noun)):-

        fronttoken(STR,Noun,Rest),

        (Noun).

 

    s_verb_phrase(Str, verb_phrase(Verb,N_Phrase)):-

        fronttoken(Str,Verb,Rest1),

        v(Verb),

        s_noun_phrase(Rest1,"",N_Phrase).

 

    s_verb_phrase(Str,verb(Verb)):-

        fronttoken(STR,Verb,""),

        v(Verb).

 

/* determiner */

 

    d("the").

    d("a").

 

/* nouns */

 

    n("bill").

    n("dog").

    n("cat").

    /* verbs */

    v("is").

Load and run this program, and enter the following goal:

    Goal s_sentence("bill is a cat", Result).

The program will return:

    Result = s(noun("bill"),verb_phrase("is", noun_phrase("a","cat")))
    1 Solution

Summary

These are the important points covered in this chapter:

1.  Visual Prolog's string-handling predicates are divided into two groups: basic string manipulation and string type conversions.

2. The predicates for basic string manipulation are summarized here:

a.  frontchar, fronttoken, and concat for dividing a string into components, building a string from specified components, and testing if a string is composed of specified components; these components can be characters, tokens, or strings

b.  subchar and substring for returning a single character from, or a part of, another string

c.  searchchar and searchstring for finding the first occurrence of a character, or a string, in a string

d.  str_len for verifying or returning the length of a string, or creating a blank string of specified length

e.  frontstr for splitting a string into two separate strings

f.   isname for verifying that a string is a valid Visual Prolog name

g.  format for formatting a variable number of arguments into a string variable

3.  The predicates for type conversion are listed here:

a.  char_int for converting from a character to an integer, or vice versa

b.  str_char for converting a single character into a string of one character, or vice versa

c.  str_int for converting from an integer to its textual representation, or vice versa

d.  str_real for converting from a real number to a string, or vice versa

e. upper_lower for converting a string to all upper-case or all lower-case characters, or testing case-insensitive string equality

f.  term_str for conversion between arbitrary domains and strings