The use of cut
 The ! at work
Try the following example (taken from Paul Brna, "Prolog Programming:
a first course"):
 
a(X):-b(X),c(X).
b(1).
b(4).
c(X):-d(X),!,e(X).
c(X):-f(X).
d(X):-g(X).
d(X):-h(X).
e(3).
f(4).
g(2).
h(1).
When the ! is executed, it succeeds and causes two side effects:
- 
backtracking cannot redo any of the subgoals to the left of the ! (i.e. the
unifications made in the predicates to the left of the ! are frozen);
-  
backtracking cannot use any other clause to satisfy the predicate
that is the head of the clause containing the ! (i.e. clauses for 
the same predicate not yet used are pruned).
In the example above, this means that onced(1):-h(1) succeeds,
then d(1) is frozen and on backtracking no other way to achieve it 
will be attempted.  Also the clause c(X):-f(X) is pruned.
So, when there is no way of satisfying e(1), backtracking will not
attempt to use the clause c(X):-f(X) (which has been pruned from 
the search space) and will not attemp to satisfy d(1) differently
(it has been frozen).  Backtracking goes back to the parent clause
a(X):-b(X),c(X) of the clause with ! and attempts to satisfy
b(X) differently.  After b(4) succeeds, 
d(4) fails.  Since the ! has not been executed, the
next clause c(X):-f(X) is used, which succeeds.
The trace below shows the steps.
[trace] 3 ?- a(X).
   Call:  (  7) a(_G310) ? creep
   Call:  (  8) b(_G310) ? creep
   Exit:  (  8) b(1) ? creep
   Call:  (  8) c(1) ? creep
   Call:  (  9) d(1) ? creep
   Call:  ( 10) g(1) ? creep
   Fail:  ( 10) g(1) ? creep
   Redo:  (  9) d(1) ? creep
   Call:  ( 10) h(1) ? creep
   Exit:  ( 10) h(1) ? creep
   Exit:  (  9) d(1) ? creep
   Call:  (  9) e(1) ? creep
   Fail:  (  9) e(1) ? creep
   Fail:  (  8) c(1) ? creep
   Redo:  (  8) b(_G310) ? creep
   Exit:  (  8) b(4) ? creep
   Call:  (  8) c(4) ? creep
   Call:  (  9) d(4) ? creep
   Call:  ( 10) g(4) ? creep
   Fail:  ( 10) g(4) ? creep
   Redo:  (  9) d(4) ? creep
   Call:  ( 10) h(4) ? creep
   Fail:  ( 10) h(4) ? creep
   Fail:  (  9) d(4) ? creep
   Redo:  (  8) c(4) ? creep
   Call:  (  9) f(4) ? creep
   Exit:  (  9) f(4) ? creep
   Exit:  (  8) c(4) ? creep
   Exit:  (  7) a(4) ? creep
X = 4 
 Examples of green and red cut
 
/* min(?X,?Y,?Min) finds the minimum of X and Y */
min(X,Y,X):- X=<Y.
min(X,Y,Y):- Y<X.
/* this is more efficient and correct - green cut */
min(X,Y,X):- X=<Y,!.
min(X,Y,Y):- Y<X,!.
/* this is incorrect - red cut 
    example ?-min(2,5,5) returns yes */
min(X,Y,X):- X=<Y,!.
min(X,Y,Y).
/* this is correct but hard to read - green cut */
min(X,Y,Z):- X=<Y,!,Z=X.
min(X,Y,Y).
/* member(?X,?L) */
member(X,[X|_]).
member(X,[_|L]):-member(X,L).
/* this is more efficient but incorrect - red cut 
   example ?-member(X,[1,2,3]) will return X=1 and fail after 
   This is a variant of the membercheck predicate listed below */
member(X,[X|_]):-!.
member(X,[_|L]):-member(X,L).
/* membercheck(+X,+L) check if X is a member of L */
membercheck(X,[X|_]).
membercheck(X,[Y|L]):- \+Y=X,membercheck(X,L).
/* more efficient but incorrect - red cut 
   example ?- membercheck(X,[1,2,3]). returns X=1  */
membercheck(X,[X|_]):-!.
membercheck(X,[Y|L]):-membercheck(X,L).
 More on cut
/*THE CUT AFFECTS ONLY THE CLAUSE IN WHICH IT IS USED */
/* once(G) disables only local backtracking in G.  Once commits to the
   first solution found for G, by disabling backtracking to G and the 
   parent goal once.
   Backtracking is not affected in the clause that calls once */
once(Goal):-Goal,!.
/* example
   ?-member(X,[a,b]),once(member(Y,[a,b,c])).
     X=a
     Y=a;
     X=b
     Y=a;
     no
   ?-member(X,[a,b]),!,member(Y,[a,b,c]).
     X=a
     Y=a;
     X=a
     Y=b;
     X=a
     Y=c;
     no
*/
/* NEGATION AS A FAILURE */
/* the combination of cut and fail produces negation as a failure. */
different(X,X):-!,fail.
different(X,Y).
/* not is predefined in prolog as \+.  Here is how it could be defined */
not(P):-P,!,fail.
not(P).
/* it is important to be careful with the use of negation as this
   simple example shows */
unmarried_student(X):- \+married(X), student(X).
student(bill).
married(joe).
/* X=joe satisfies married(X), so the negation fails.
   ?-unmarried_student(X).
   no
Changing the order of the predicates in the unmarried_student clause fixes 
the problem
unmarried_student(X):- student(X), \+married(X).
The morale: do not use not with unbound arguments */
  
/* CONTROL STRUCTURES BUILT USING CUT */
/* if P then Q else R is predefined in Prolog as P->Q;R.  
   It is not strictly needed, and can be achieved with two clauses.
   Here is how it could be defined */
P->Q;R :- P,!,Q.
P->Q;R :- R.
/* example factorial(+N,?F) */
factorial(N,F):-
	(N=<0 -> F is 1;
	 N1 is N-1, factorial(N1,R), F is R*N).