
/***** A definition of making change for $1: 
   change(Q,N,D,P)  holds true if the sum of the monetary values of
   the Q quarters, D dimes, N nickels, and P pennies totals $1.  
*/
change(Q,D,N,P) :-
    /* First, define the universe of individuals (atoms) we use:
       (these are like the "data types" of the param names) */
        member(Q,[0,1,2,3,4]),                  /* quarters     */
        member(D,[0,1,2,3,4,5,6,7,8,9,10]) ,    /* dimes        */
        member(N,[0,1,2,3,4,5,6,7,8,9,10,       /* nickels      */
                   11,12,13,14,15,16,17,18,19,20]),
        /* Next, define the constraints on the solution: */
        Sum is 25*Q +10*D + 5*N,
        Sum =< 100,
        P is 100-Sum.



/***** Making change for  HowMuch:  changeFor(HowMuch, Q,N,D,P)
   holds true if the sum of the monetary values of the Q quarters,
   D dimes, N nickels, and P pennies totals  HowMuch
*/
changeFor(HowMuch, Q,D,N,P) :-
        /* we list the atoms in order of preference for use: */
        member(Q,[5,4,3,2,1,0]),     /* quarters     */
        member(D,[5,4,3,2,1,0]),     /* dimes        */
        member(N,[4,3,2,1,0]),       /* nickels      */
        member(P,[4,3,2,1,0]),       /* pennies      */
        HowMuch is 25*Q +10*D + 5*N + P.




/***** Defining sorting as an ordered permutation of a list: */

/* select(X, HasAnX, HasOneLessX)  "extracts" X from  HasAnX,
   giving HasOneLessX.  (That is,  [X|HasOneLessX]  is a permutation
   of  HasAnX.)  The definition is built into Prolog, but here it is, anyway:

select(X, [X|Rest], Rest).
select(X, [Y|Ys], [Y|Zs]) :- select(X, Ys, Zs).
*/

/* permutation(Xs, Zs)  holds true if Zs is a reordering of Xs */
permutation([], []).
permutation(Xs, [Z|Zs]) :- select(Z, Xs, Ys),  permutation(Ys, Zs).

/* ordered(Xs) holds true if the elements in Xs are ordered by < */
ordered([]).
ordered([X]).
ordered([X,Y|Rest]) :- X =< Y,  ordered([Y|Rest]).

/* sorted(Xs, Ys)  holds when  Ys  is the sorted variant of Xs */
sorted(Xs, Ys) :- permutation(Xs, Ys), ordered(Ys).




/***** Refining the definition of  select,  yielding selection sort: */

/* selectLeast(X, Ys, Zs)  if  X  is the least element in list Ys  and  [X|Zs]  is a permutation of  Ys,  that is,  Zs  is  Ys  with  X  removed. 
*/
selectLeast(X, [X], []).
selectLeast(X, [Y|Ys], [Y|Zs]) :-  selectLeast(X, Ys, Zs), X < Y.
selectLeast(Y, [Y|Ys], [X|Zs]) :-  selectLeast(X, Ys, Zs), Y =< X.

/* permutation  stays the same, as does  ordered  and  sorted: 
   (but note use of  selectLeast)  */
permutationL([], []).
permutationL(Xs, [Z|Zs]) :- 
                    selectLeast(Z, Xs, Ys),  permutationL(Ys, Zs).

sortedL(Xs, Ys) :- permutationL(Xs, Ys), ordered(Ys).




/***** Refining the definition of  permutation,  giving insertion sort: */

/* insert(X, L, LwithX)  inserts element X into ordered list L, generating ordered list,  LwithX */
insert(X, [], [X]).
insert(X, [Y|Ys], [X, Y | Ys]) :-  X =< Y.
insert(X, [Y|Ys], [Y|Zs]) :-  X > Y,  insert(X, Ys, Zs).

/* permuationI(Xs, Ys)  uses  insert  to generate list Ys as a permutation of list Xs:  */
permutationI([], []).
permutationI([X|Xs], Ys) :-  
                 permutationI(Xs, Zs), insert(X, Zs, Ys).

sortedI(Xs, Ys) :- permutationI(Xs, Ys), ordered(Ys).

