home *** CD-ROM | disk | FTP | other *** search
- /* This program modified by Bob Morein 3/1/86. */
-
-
- mem(X, [X|_] ).
- mem(X,[_|Y] ) :- mem(X, Y).
-
- anymem(X,Y) :- mem(X,Y),!.
-
- ppt( [H|T], I ) :- !, J is I+3, ppt(H, J), ppxt(T, J), nl.
- ppt( X, I ) :- tab(I), print(X), nl.
-
- ppxt( [], _ ).
- ppxt( [H|T], I ) :- ppt(H, I), ppxt(T, I).
-
- affirm(Choice) :-
- print(Choice),
- print(' (y/n) ?>>'),
- get0(C),
- mem(C,"yY").
-
- /* ------------ core of dial_411 program -------------*/
- query(Last,First,Address) :-
- nl,nl,
- print('Enter query data with entry format:'),nl,
- print('Last Name >>'),
- ratom(Last),
- print('First Name >>'),
- ratom(First),
- print('# or Address >>'),
- ratom(Address).
-
- search(Ll,Ff,Aa) :-
- print('\nseeking... '),
- data( H ),
- [L,F,A] = H,
- ( Ll = [] ; anymem(Ll,L) ),
- ( Ff = [] ; anymem(Ff,F) ),
- ( Aa = [] ; anymem(Aa,A) ),
- nl, ppt(H,0),
- affirm('\nStop searching this query'), !.
- search(L,Ff,Aa) :-
- print('\nThis search over, no (more) matches on the query.').
-
- direct :-
- repeat,
- query(A,B,C),
- search(A,B,C), fails,
- affirm('\nQuit directory').
-
- /* lead-off predicate */
- dial_411 :-
- directory_message,
- affirm('\n\nContinue with directory, and initiate a query/search '),
- direct,
- print('\nQuitted directory.'),
- !,fails.
- dial_411 :- print('\nQuitted directory.'),!,fails.
- /* ----------------------- end core -------------------------------*/
-
- /* ----------------- start directory_message ------------------------------ */
- directory_message :-
-
- print('\nThe program "directory" gets you directory information by household.'),
- print('\nThe data of each household are in 3 categories :'),
- print('\n 1)last names, e.g. Blacquier' ),
- print('\n 2)first names, Fred '),
- print('\n 3)phone # & address lines Carlisle OR 01741 .'),
- nl,
- print('\nTo query directory, enter ONE datum for EACH category.'),
- print('\nDirectory then seeks a match with these data, e.g. with: '),
- print('\n last name>><Return> (wildcard datum) '),
- print('\n first name>><Return> (wildcard datum) '),
- print('\n # & address>> \'Carlisle\'. <Return> .'),
- nl,
- print('\nEntry spellings & Caps must match in the database EXACTLY, or they fails.'),
- print('\nWILDCARD datums always succeed (being anonymous variables).'),
- print('\nA wildcard entry is a carriage return.'),
- print('\nClose your entries and replies with a <Return> .'),
- nl,
- print('\nSome queries (esp. wildcards) can generate multiple matches. The '),
- print('\ninterpreter will ask if you seek more matchups to a query, or not.'),
- print('\n to STOP this program use: <Esc> OR <Ctrl-C>'),
- print('\n to QUIT Pdprolog use: ?-exitsys.').
- /* --------------------- end message ----------------------------------- */
-
- /* --------------- start, directory household data --------------------- */
-
- data([
- ['ADA'],
- ['Robert Morein'],
- ['215/646-4894','1570 Arran Way','Dresher','PA','19025']
- ]).
- data([
- ['Brown'],
- ['Amy'],
- ['953-8626', '61 College Ave', 'Medford', '02138']
- ]).
-
- /* ---------------- end, directory household data --------------------- */
-
- ?-directory_message, direct.
-