CS 342 Lecture -*- Outline -*- * Real Prolog ** real Prolog syntax (see page 386) clause (infer G from H K) is written G :- H,K. term (p e1 e2) is written p(e1,e2) query (infer? (p Y) (print Y)) is written ?- p(Y). comments start with % syntax for lists: [] nil [x|y,z] (cons x (cons y (cons z nil))) Prolog prints substitution if goal is satisfied, can also ask for other ways to satisfy goal (;) prints "no" if no ways to satisfy goal ** Examples in Prolog syntax *** Lists in Prolog ------------ % find last element of a list find_last(X, [X]). find_last(X,[_|Y]) :- find_last(X,Y). ?- find_last(X,[a,b,c]). % Value: X = c ------------- *** Peano arithmetic in Prolog ---------- % s(0) represents 1, s(s(0)) represents 2, etc. sum(0,X,X). sum(s(X),Y,s(Z)) :- sum(X,Y,Z). prod(0,X,0). prod(s(X),Y,Z) :- prod(X,Y,W), sum(Y,W,Z). % division quotient(X,Y,Z) :- prod(Y,Z,X). % comparisons lessthan(0,s(I)). lessthan(s(I),s(J)) :- lessthan(I,J). equal(0,0). equal(s(I),s(J)) :- equal(I,J). lessthanequal(I,J):- equal(I,J). lessthanequal(I,J):- lessthan(I,J). % generation of numbers in a closed interval generate(I,J,K) :- lessthanequal(I,K), lessthan(K,J). generate(I,J,K) :- lessthanequal(I,K), equal(K,J). ------------- ** Control in Prolog *** Cut (!) ------- % recursive program for membership in lists mbr(Head, [Head|_]). mbr(Element,[_|Tail]) :- mbr(Element,Tail). ------- If only want membership test, want to stop as soon as found something. use cut (!, in first clause) ------- % membership test mbr1(Head, [Head|_]):- !. mbr1(Element,[_|Tail]) :- mbr1(Element,Tail). ------- second clause used only if first fails. cannot generate several different answers. ------ % a transcript | ?- mbr(2,X). X = [2|_6] ; X = [_5,2|_10] ; X = [_5,_9,2|_14] | ?- mbr1(2,X). X=[2,_6] ; no ------ **** Backtracking across cut causes whole clause to fail (fail to caller) p :- a, b, c. b :- d, e, !, f. **** think of cut as committing Prolog to a choice the goal succeeds and commits Prolog to all the choices made since the parent goal was unified with the head of the clause in which the cut occured. thus: prunes all clauses below it prunes all alternatives to its left in a clause. does not affect goals to its right in a clause. example: If b1 then b2 else b3 can be done using cut as follows a1 :- b1, !, b2. a1 :- b3. *** Negation as failure **** negation treated as unprovability (closed world assumption) not combines cut and fail (predicate that fails) ------------------ not(X) :- X, !, fail. not(X). ------------------ order essential (bad in itself, since less modular) idea is that if goal fails finitely, not succeeds but Prolog doesn't even find finite failures for sure note: if foo terminates, so does not(foo) if foo does not terminate, not(foo) may or may not halt **** good programming style avoids cut-fail, since logic disappears. difference between proving something false not being able to prove it's true(closed world) **** "not" doesn't work correctly for non-ground goals -------- unmarried_student(X) :- not(married(X)), student(X). student(bill). married(joe). ?- unmarried_student(X). no --------- X=bill should be a solution. not(married(X)) tries married(X), finds X=joe, so married succeeds, causing not(married(X)) to fail (don't try again because of cut!) (solved by reversing order of goals) double negation doesn't work as one expects ** Other non-logical stuff in Prolog *** is: allows one to use computer's arithmetic K is M+1 like assignment K := M+1 *** asserta, assertz: put rules in database *** retract: takes rule out of database allow non-monotonic reasoning, memoization, assignment