home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Simtel MSDOS 1992 December
/
simtel1292_SIMTEL_1292_Walnut_Creek.iso
/
msdos
/
aijournl
/
ai_apr88.arc
/
APRIL.CDE
next >
Wrap
Text File
|
1988-03-25
|
16KB
|
473 lines
%-----------------------------------------------------------------------
%-----------------------------------------------------------------------
% A Simple Query Processor in Prolog
%
% Author: Rodger Knaus
% Instant Recall
% 5900 Walton Rd.
% Bethesda, Md. 20817
% (301) 530 - 0898
% BBS: (301) 983-8439 (2400 bps)
%
% Version of Prolog: Arity Prolog, v. 4
%
% See the Practical Prolog column in
% AI Expert (April, 1988) for a discussion of this program
%
% Note about this listing: This listing is complete except
% for a few low level predicates, such as list_length which
% you can easily write yourself.
%
%
%-----------------------------------------------------------------------
%-----------------------------------------------------------------------
%-----------------------------------------------------------------------
%
% Listing 1 -- The top Level of a Query Processor
%
%
% Call: process_query( Field_list, Tables, Conditions)
%
% Purpose: Retrieves data in the Prolog database specified by
% Field_list, Tables, and Conditions
%
% Input arguments:
%
% Field_list = list of fields to be displayed
%
% Tables = list of predicate names for the facts which
% contain the fields in Field_list.
%
% Conditions = a list of boolean conditions which the retrieved
% data are to satisfy
%
% Output arguments:
%
% none
%
% Success conditions:
%
% Succeeds whenever the input arguments can be translated into
% a query in Prolog.
%
% Effects:
%
% When the input arguments can be translated into Prolog, any
% data retrieved by the query in Prolog is displayed. If the
% translation can not be carried out, an error message is
% displayed.
%
%
% try to retrieve data
process_query(Field_list, Tables, Conditions ) :-
% translate inputs into a Prolog question
generate_query( Field_list, Tables, Conditions, Generated_goal),!,
% With the Prolog question, retrieve and display data
get_all( Field_list, Generated_goal),
% Stay with this rule if it succeeds
!.
% put out error message if previous rule fails
process_query( Field_list, Tables, Conditions) :-
nl, write( $Error in process_query for :$),
nl, write( $Field_list = $ ), write( Field_list ),
nl, write( $Tables = $ ), write( Tables ),
nl, write( $Conditions = $ ), write( Conditions ),
nl, fail.
%
%-----------------------------------------------------------------------
%
%----------------------------------------------------------------------
% |
% Listing 2 -- Predicate for Defining a Data Retrieval Predicate |
% |
generate_query(Field_list, Tables, Conditions, prdbms_goal(X)) :- %
% Step 1 -- retract all temporaryy information left from %
% processing previous queries %
retract_old_clauses, !, %
% Step 2 -- construct list of calls for table rows %
% that contain the needed information %
get_calls_to_tables(Field_list, Tables, Table_calls), !, %
% Step 3 -- translate conditions to Prolog %
build_conditions_terms( Table_calls, Conditions,
Condition_terms), !, %
% Step 4 -- build list of variables representing
% list of fields
replace_field_names( Table_calls,
Field_list,
Variable_list),
% Step 5 -- term setting variable in rule head
Goal_term = ( X = Variable_list ),
% Step 6 -- build list of terms in prdbms_goal rule body %
append_lists( [ Table_calls, %
Condition_terms, %
[ Goal_term ] ], %
Rule_body_as_list), !, %
% Step 7 -- Build a conjunction of rule body terms %
build_conjunction( Rule_body_as_list, Body ), !, %
% Step 8 -- assert a new rule for predicate goal %
asserta( (prdbms_goal(X) :- Body)) .
% |
%----------------------------------------------------------------------
%
%---------------------------------------------------------------------------
%
% Listing 3 -- Retracting Old Information from the Database
%
%/****************** retract_old_clauses *****************************/
%/*
%retract_old_clauses retracts facts and rules which might be left
% from processing previous user queries.
%*/
%
retract_old_clauses :-
% retract rules that are Prolog implementations of old queries
retract_all_clauses(prdbms_goal, 1),
% retract old variable dictionary facts
retract_all( temp_variable_meaning( _ , _)).
%
%/****************** retract_all_clauses *****************************/
%/*
% Call: retract_all_clauses(Functor, Arity)
%
% Purpose: retracts all clauses whose head has a given functor and arity.
%
% Input arguments:
%
% Functor: Functor for the head of rules to be retracted
%
% Arity: Arity of functor of head of rules to be retracted
%
% Output arguments: none
%
% Success conditions: always succeeds
%
% Effect: retracts all clauses with head functor Functor of arity Arity
%
% Example:
%
% retract_all_clauses(factorial, 2) retracts any rules in the database
% of the form
%
% factorial(_,_) :- _.
% */
%
retract_all_clauses(Functor, Arity) :-
% build a term with Functor/Arity as functor and
% all different variables as arguments
functor(Head, Functor, Arity),
% build a rule with head Head and arbitrary tail
Rule = ( Head :- _),
% retract everything that matches Rule
retract_all(Rule).
%
%/****************** retract_all ************************************/
% /*
% Call: retract_all(Form)
%
% Input arguments:
%
% Form = a Prolog term such that anything which matches it is to be
% retracted from the Prolog database
%
% Success conditions: always succeeds
%
% Effect: retracts any clause that matches Form from the database
% */
%
retract_all(Form):- retractall(Form).
retractall(Form):-
repeat,
retractall1(Form). /* Fails until no more patterns match Form */
% if there is something in the database matching Form,
retractall1(Form):-
% retract it,
retract(Form),
% cut to stay in this rule
!,
% and fail to cause backtracking back up to get another Form
fail.
% if nothing else matches Form, then succeed
retractall1(_):-!.
%
%
%---------------------------------------------------------------------------
%---------------------------------------------------------------------------
%
% Listing 4 -- Replacing Field Names with Values
%
% /*
% Call:
%
% replace_field_names( Input_structure, Output_structure)
%
% Input argument:
%
% Input_structure = a Prolog structure containing field names
%
% Output argument:
%
% Output_structure = the corresponding structure with field names
% replaced by variables.
%
% Success conditions: always succeeds
%
% Side Effects: none
%
% Example:
%
% Assumptions: The database contains
%
% temp_variable_meaning( item, X1).
% temp_variable_meaning( quantity, X4).
%
% Call: replace_field_names( [(item = diskettes), (quantity > 5) ],
% Result)
%
% On exit:
%
% Result = [(X1 = diskettes), (X4 > 5) ]
%
%
% */
% map variables into themselves
replace_field_names( _, Input, Input ):-
var( Input), !.
% map atoms
replace_field_names( Table_calls, Input, Result):-
atomic( Input), !,
replace_field_name_atom( Table_calls, Input, Result).
% map the empty list into itself
replace_field_names( _, [], []):- !.
% map lists recursively
replace_field_names( Table_calls, [ H | T ], [H1 | T1 ]):- !,
replace_field_names( Table_calls, H, H1),
replace_field_names( Table_calls, T, T1).
% map functor and argument structures
replace_field_names( Table_calls, Structure, Result ):-
% map structures by first changing them to lists,
Structure =.. Input_list,
% then mapping them,
replace_field_names( Table_calls, Input_list, Result_as_list),
% finally changing them back to structures
Result =.. Result_as_list, !.
% report error if this rule is reached
replace_field_names(_, Structure, Structure ):-
nl,
write($This structure could not be mapped by replace_field_names:$),
nl, write(Structure).
/* Using this predicate we can define the helper predicate
that translates user-supplied conditions into Prolog */
build_conditions_terms( Table_calls,
Conditions,
Condition_terms) :-
replace_field_names( Table_calls,
Conditions,
Condition_terms).
/* The next predicate maps atoms for 'build_conditions_terms',
replacing field names with the corresponding variable
*/
% Strategy is recursion on the list of Tables
% default mapping of an atom is the atom
replace_field_name_atom( [], Input, Input) :- !.
% try to find the variable for Field in Table
replace_field_name_atom( [Table | Tables], Field, Result) :-
% get the name of the functor of Table
functor(Table, Predicate_name, _),
% see if Field is in this table
% if so, get its argument Position
call(has_field( Predicate_name, Field, Position)), !,
% get the corresponding variable Result from Table
arg(Position, Table, Result).
% if no success above, try the next table
replace_field_name_atom( [ _ | Tables], Input, Result) :-
replace_field_name_atom( Tables, Input, Result).
% |---------------------------------------------------------------------------
%-------------------------------------------------------------------------
%
% Listing 6 -- Building a Conjunction from a List of Terms
%
% /*
% Call: build_conjunction( List, Conjunction)
%
% Input arguments:
%
% List = a list of terms
%
% Output arguments
%
% Conjunction = the list of terms ANDed together.
%
% Success conditions:
%
% Succeeds whenever the input is a list.
%
% Note: This predicate also works in the opposite direction, converting
% a conjunction to a list of terms.
%
% */
% the AND of no items is always true
build_conjunction( [], true):-!.
% the AND of one item is the item itself
build_conjunction( [Term], Term) :- !.
% Here is the recursive rule
build_conjunction( [ Term | Terms ], ( Term , Terms_as_conjunction)) :-
build_conjunction( Terms , Terms_as_conjunction).
%-------------------------------------------------------------------------
%----------------------------------------------------------------------
%
% Listing 7 -- A Data Retrieval Loop
%
% /*
% Call: get_all(Field_list, Goal )
%
% Input arguments:
%
% Field_list = list of names of user fields
%
% Goal = goal that finds a single instance of the desired data
%
% Success conditions
%
% always succeeds
%
% Effects: displays all instances of data satisfying the user query
% */
%
get_all(Field_list, Goal ) :-
call( Goal ),
arg(1, Goal , Value_list),
display_item( Field_list, Value_list),
fail.
get_all(_, _ ) :-!.
%
%----------------------------------------------------------------------
%------------------- Predicates from body of column --------------------
% gets pattern matching an arbitrary data item in a table
% Note: this is the special case when there is only one table
get_calls_to_tables(Field_list, [Table], [Table_call]) :-
find_arity(Table, Arity),
functor( Table_call, Table, Arity).
% finds the Arity of nTable_name
find_arity(Table_name, Arity) :-
findall( X, has_field(Table_name, X, _), Fields),
list_length(Fields, Arity).
% build term that sets output variable in head of generated rule
% for processing the query
build_goal_output_term( Field_list ,
Output_variable,
Goal_output_term) :-
% get list of variables
replace_field_names( Field_list , Varible_list),
% build the output term
Goal_output_term = ( Variable = Varible_list ).
% a simple display predicate for a table row
display_item( Field_list, Value_list) :-
nl, write( Value_list).
% Since we are assuming a single table call, we omit the definition
% of 'find_table_call_for_field'. In this special case you can use
find_table_call_for_field(_, [Table_call], Table_call).
% -------------------------------------------------------------------------
%-------------------- End of program --------------------------------
%------------------ Start of test data and predicates ------------------
/********** test database *************************************************/
transaction( diskettes, 1, 1/24, 100, 24.95,
$Dicount Diskettes$, $Visa4$ ).
transaction( 'hard disk', 2, 2/13, 1, 345.00,
$Computer Serv. Ctr.$, $Visa$).
transaction( eyeglasses, 3, 2/14, 1, 250.00,
$Dr. Feinberg$, $check 345$).
supplier( $Dicount Diskettes$,
address( [$Box 2314$, $Chicago, Ill.$], _ ),
[diskettes, ribbons, paper]).
supplier( $Computer Serv. Ctr.$,
address( [$5211 Nebraska Ave. NW$, $Wash. D.C.$], $20015$ ),
'hard disk').
supplier( $Dr. Feinberg$,
address( [$4545 Conn. Ave. NW$, $Wash. D.C.$], $20016$),
eyeglasses).
item( diskettes , supplies ).
item( 'hard disk' , 'capital expenditures' ).
item( eyeglasses , 'medical expenses' ).
/************************** data dictionary ******************************/
% This is a data dictionary for the above database
has_field(transaction, item, 1).
has_field(transaction, id, 2).
has_field(transaction, date, 3).
has_field(transaction, quantity, 4).
has_field(transaction, price, 5).
has_field(transaction, supplier, 6).
has_field(transaction, 'how paid', 7).
has_field(supplier, name, 1).
has_field(supplier, address, 2).
has_field(supplier, items, 3).
has_field(item, item, 1).
has_field(item, class, 2).
/************************** test predicates ******************************/
% This is a test predicate for process_query. It should produce the
% following output on the screen with the example data above:
% [diskettes, 1/24 ]
test :-
process_query( [ item , date],
[ transaction ] ,
=( item, diskettes) ).
/********************** end test predicates ******************************/
%------------------- End of listing ------------------------------------
te