home *** CD-ROM | disk | FTP | other *** search
- /* ----------------------- message ----------------------------->
- CARDFILE January 1986
-
- author: George Planansky
- 11 Varnum St.,
- Arlington, MA 02174
-
- written using A.D.A. PD PROLOG.
-
- This little program demonstrates how functor, arg, and assertz may be
- to construct, store, & access data-bearing PROLOG structures.
-
- First, notice that lines #1 & #2 of get_book are functionally equivalent,
- and may be substituted for each other. IF the predicate book had many
- arguments, instead of only the 2 used here, line # 1 would be more convenient
- and definitive than, say, book(T,_,_,_,_,_,_,_,_,_,_,_,_,_).
- Clocksin & Mellish point this out while discussing the predicate arg.
-
- Second, notice that there are basically two ways that a value, or a
- value-bearing structure, may be accessed in PROLOG:
-
- 1. by being invoked, passed, and shared as an argument of structures ...
- e.g., the argument Y of get_book(Y,T,A).
- 2. by being in a structure in the database, which structure may be matched,
- deleted with retract, and emplaced with asserta or assertz.
- e.g., the lack of an argument Y in alt_get_book(T,A).
-
- Method 1 is used by the program alt_card_file,
- method 2 is used by card_file.
-
- Notice that using a conjunction of the type:
-
- retract(Y), process(Y,Component_Yn), assertz(Y)
-
- makes a DESTRUCTUVE reassignment to the value of Y (regarding one of its
- components) in the database. PROLOG can so use its (global) constants
- to emulate the global variables of languages like BASIC and Pascal.
-
- The program squares in file SQR_GAME uses the variable Gr as a "ubiquitous"
- variable, and so Gr is among the arguments of many of the predicates there.
- The structure square(Id,Si,Ad,En,Ow) there is a "global" variable.
-
-
- TO RUN:
-
- CARDFILE.PRO and PDPROLOG.EXE must be in the active MS/PC -DOS directory.
-
- Invoke the interpreter with the DOS command:
- >"PDPROLOG <Return>"
-
- Command the interpreter to load and run cardfile:
- ?-"consult(cardfile). <Return>"
-
- Note that the query ending CARDFILE.PRO instructs the interpreter to print
- a message suggesting the clause "card_file" as a response.
- <------------------------------------------------------------------- */
-
- is_a_book(X) :- functor(X,book,2).
-
- title(X,T) :- is_a_book(X), arg(1,X,T).
-
- author(X,A) :- is_a_book(X), arg(2,X,A).
-
- get_book(T,A) :-
- is_a_book(Y), title(Y,T), author(Y,A), Y, /* #1 */
- /* book(T,A), */ /* #2 */
- print('\n\ntitle: ',T,' \nauthor: ',A),
- print('\nGet more books (y/n)?>>'),
- read(Yes),
- Yes \= y,
- !, fail.
- get_book(T,A) :- print('Out of books'),
- !, fail.
-
- enter_book(T,A) :- is_a_book(Y),
- title(Y,T), author(Y,A),
- assertz(Y).
-
- card( in) :- print('\nenter title>>'),
- read(T),
- print('\nenter author>>'),
- read(A),
- enter_book(T,A),
- !, fail.
- card(out) :- print('\nenter title>>'),
- read(T),
- print('\nenter author>>'),
- read(A),
- get_book(T,A).
-
- card_file :- repeat,
- print('\nCardfile: enter task (in/out) >>'),
- read(Task),
- card(Task).
-
- alt_get_book(Y,T,A) :- Y,
- print('\n\ntitle: ',T,' \nauthor: ',A),
- print('\nGet more books (y/n)?>>'),
- read(Yes),
- Yes \= y,
- !, fail.
- alt_get_book(Y,T,A) :- print('Out of books'),
- !, fail.
-
- alt_enter_book(Y) :- assertz(Y).
-
- alt_card( in) :- print('\nenter title>>'),
- read(T),
- print('\nenter author>>'),
- read(A),
- is_a_book(Y),
- title(Y,T), author(Y,A),
- alt_enter_book(Y),
- !, fail.
- alt_card(out) :- print('\nenter title>>'),
- read(T),
- print('\nenter author>>'),
- read(A),
- is_a_book(Y), title(Y,T), author(Y,A),
- alt_get_book(Y,T,A).
-
- alt_card_file :- repeat,
- print('\nCardfile: enter task (in/out) >>'),
- read(Task),
- alt_card(Task).
- /**/
- ?- nl,
- print('\nThis is cardfile. You can enter books into, and seek books from, the '),
- print('\ndatabase IN MEMORY. Do this by choosing a task and then entering '),
- print('\nthe specified data. Data entries follow a format:'),
- print('\n either " onewordnoncap ", '),
- print('\n or " \'two or more words\' ", '),
- print('\n or " \'Onecapitalizedword\' ".'), nl,
- print('\nThat is, anything but a single word uncapitalized entry must be put '),
- print('\nin single quotes.'), nl,
- print('\nAlso, terminate each entry with a period and a <Return>.'),nl,
- print('\nSeek a book by entering KNOWN data exactly as above.'),
- print('\nSpecify UNKOWN or "wildcard" data with the underline key: "_".'),
- print('\nLibrary will attempt matches of data to the database.'),
- print('\n\nStart cardfile with: ?- "card_file. <Return>" .'),
- print('\nYou may quit library by pressing <Esc>, and you may quit PROLOG to MS-DOS'),
- print('\nwith: ?- "exitsys. <Return>" .').
- /**/