home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Power-Programmierung
/
CD1.mdf
/
prolog
/
library
/
prolo_c
/
exampl63.pro
< prev
next >
Wrap
Text File
|
1986-10-06
|
3KB
|
89 lines
/*Program 63*/
/*
The names of the variables are changed
from the manual to add clarity.
*/
code = 1000 trail = 1000
domains
arg = reference var(vid); symb(symbol); fntr(fid, arglist)
arglist = reference arg*
atom = atom(aid, arglist) /* atom: is a predicate and arguments */
atomlist = atom*
bind = b(vid, arg) /* bind: is a variable and the
term(arg) bound to it */
b_list = reference bind* /* variable binding list */
fid, aid, vid = symbol /* fid: is functor name */
/* aid: is atom name */
/* vid: is variable name */
database
clause(atom, atomlist)
predicates
call(atom)
unify_arg(arg, arg, b_list)
unify_arg_list(arglist, arglist, b_list)
unify_subgoals(atomlist, b_list)
member(bind, b_list)
goal
makewindow(1,6,3,"The solution",10,9,12,63),
write("Remove this goal and enter the other goals on page 150\n\n"),
call(atom(likes,[Name,Activity])),
write(Name,Activity),nl,
fail.
clauses
call(atom(Id, Arglist)) :-
clause(atom(Id,Arglist1), Body), /* lookup clause */
free(B_list), /* all variables are free */
unify_arg_list(Arglist, Arglist1, B_list),
unify_subgoals(Body, B_list).
/*
unify_arg_list unify the argument list in a clause
*/
unify_arg_list([], [], _).
unify_arg_list([Arg1|ArgLst1],[Arg2|ArgLst2],B_list) :-
unify_arg(Arg1, Arg2, B_list),
unify_arg_list(ArgLst1, ArgLst2, B_list).
/*
unify_arg match the arguments in atom and assign variables
*/
unify_arg(Arg, var(X), B_list) :-
member(b(X,Arg),B_list), !.
unify_arg(symb(X), symb(X), _). /* symbols match */
unify_arg(fntr(Id, Lst1), fntr(Id,Lst2),Bind) :- /* functor & */
unify_arg_list(Lst1, Lst2, Bind). /* arguments match */
/*
unify_subgoals unification down the goal stack
*/
unify_subgoals([],_).
unify_subgoals([atom(Id,ArgLst)|AtomLst],B_list) :-
unify_arg_list(Call,ArgLst,B_list), call(atom(Id,Call)),
unify_subgoals(AtomLst,B_list).
member(X,[X|_]).
member(X,[_|Lst]) :-
member(X,Lst).
/*
DATABASE FACTS ASSERTED
facts can either be asserted on the fly or as part of
the code as shown here.
*/
clause(atom(likes,[symb(ellen),symb(tennis)]), []).
clause(atom(likes,[symb(john),symb(football)]), []).
clause(atom(likes,[symb(eric),symb(swimming)]), []).
clause(atom(likes,[symb(mark),symb(tennis)]), []).
clause(atom(likes,[symb(bill),var(x)]),
[atom(likes,[symb(tom), var(x)])]).