CSC 372, Spring 2023 Assignment 6 Due: Friday, April 7, 2023 at 23:59:59

The Usual Stuff

About the if-then-else structure (->) and disjunction (;)

The rules about using if-then-else and disjunction are the same as for assignment 5.

General advice

If you think you need to use arithmetic or something like between on rotate, outin, and/or btw, you're probably not understanding how Prolog naturally generates alternatives. The slides have code for a number of predicates that generate alternatives but sf_gen on slides 193-194 was included specifically to help with outin and btw.

once/1

Various tests run by the tester use the higher-order predicate once(Goal), which limits Goal to producing one result. Example:
?- once(nth0(Pos, [a,b,a,c,a], a)).
Pos = 0.

Potential alternatives that don't materialize

For some problems the tester is not sensitive to potential alternatives that don't materialize. Consider this behavior for lst, from the first problem below.

?- lst([1,2,3],X).
X = 3 ;
false.
It prompts because somewhere there's at least one more clause that can be tried. The tester won't distinguish between the above behavior and the following behavior:
?- lst([1,2,3],X).
X = 3.

Problem 1. (15 points) append.pl

Note: This problem has restrictions!

The purpose of this problem is to help you see that append/3 can be used for lots more than concatenating two lists. You are to write several simple predicates that heed this restriction: the only predicates you can use are length/2 and append/3. For some predicates, like head, a single append goal will be all you need:

head(List,Elem) :- append(...).

Additionally, you may use the [E1, E2, ..., EN] list syntax, like in append([X,Y],[],Z), but you may not use the [E1, E2, ..., EN | Tail] notation, introduced on slide 183+.

Finally, your predicates themselves may not be recursive, and they must have only one clause, a rule.

Here's a file that has some examples of predicates that violate the restrictions:

$ cat violations.pl
firstlast(L, R) :- ..., FL = [F,L]. % [F,L] is ok, but the =
                                    % predicate is also used.

min2(L) :- ..., N > 1, !.           % Uses the > and cut predicates

halves(...) :- ..., append([A,B|_], ...). % Uses [E1, ..., EN|Tail]

Here are the predicates you are to implement:

head(?List, ?Elem) expresses the relationship that the first element of List is Elem. It fails if the list is empty.

?- head([a,b,c],H).
H = a.

?- head([a,b,c],x).
false.
lst(?List, ?Elem) expresses the relationship that the last element of List is Elem. It fails if the list is empty.
?- lst([1,2,3],X).
X = 3 ;
false.

?- lst(L,4).
L = [4] ;
L = [_G2199, 4] ;
L = [_G2199, _G2205, 4] ;
...keeps going...
init(?List, ?Init) expresses the relationship that Init is all but the last element of List. It fails if List is empty.
?- init([a,b,c,d],I).
I = [a, b, c] ;
false.
tail(?List, ?Tail) expresses the relationship that Tail is all but the first element of List. It fails if List is empty.
?- tail([a,b,c],T).
T = [b, c].
min2(+List) fails if List is not at least two elements long.
?- min2([1]).
false.

?- min2([1,2]).
true.
mem(?Elem, ?List) behaves just like the built-in member/2:
?- mem(2,[1,2,3]).
true ;
false.

?- mem(E,[1,2,3]).
E = 1 ;
E = 2 ;
E = 3 ;
false.
contains(+List, ?SubList) expresses the relationship that List contains SubList.
?- contains([1,2,3,4,5],[3,4,5]).
true ;
false.

?- contains([1,2,3,4,5],[10,20]).
false.

?- contains([1,2,3],S), S \== [].
S = [1] ;
S = [1, 2] ;
S = [1, 2, 3] ;
S = [2] ;
S = [2, 3] ;
S = [3] ;
false.
firstlast(?List, ?FL) expresses the relationship that FL is a list containing the first and last elements of List. It fails if List is empty.
?- firstlast(L,[1,2]).
L = [1, 2] ;
L = [1, _G3410, 2] ;
L = [1, _G3410, _G3416, 2] ;
...keeps going...
halves(?List, ?First, ?Last) expresses the relationship that the first half of List is First and the second half is Last. It fails if the length of List is odd.
?- halves([1,2,3,4],F,S).
F = [1, 2],
S = [3, 4] ;
false.

?- halves([1,2,3,4,5],F,S).
false.

?- halves([],F,S).
F = S, S = [] ;
false.

?- halves(L,[a,b],S).
L = [a, b, _G4635, _G4638],
S = [_G4635, _G4638].

Remember that you may only use append and length in these predicates! The Ruby program a6/check-append.rb strips away calls to append and length, and valid uses of [...]. Here's what I see when I run it on my solution:

$ a6/check-append.rb append.pl
head:-
lst:-
init:-
tail:-
min:-
mem:-
contains:-
firstlast:-
halves:-
Note that for each predicate, only the predicate name and the "neck" symbol are shown.

Here again is violations.pl, shown above, too:

$ cat violations.pl
firstlast(L, R) :- ..., FL = [F,L]. % [F,L] is ok, but the =
                                    % predicate is also used.

min2(L) :- ..., N > 1, !.           % Uses the > and cut predicates

halves(...) :- ..., append([A,B|_], ...). % Uses [E1, ..., EN|Tail]
Here's what check-append.rb shows:
$ a6/check-append.rb violations.pl
firstlast:-=
min:->!
halves:-|

Note the presence of characters following the neck symbols— they indicate a likely violation of the restrictions:

The Tester runs a6/check-append.rb as its last test for append. You can run the check by itself like this:

$ a6/t append -t check

a6/check-append.rb is new. We may find it produces some false positives. Let us know if anything looks suspicious!

Testing note

Use a6/t append.pl -t PREDICATE to test an individual predicate.

Problem 2. (3 points) splits.pl

This problem reprises splits.hs from assignment 3. Write a predicate splits(+List,-Split) that unifies Split with each "split" of List in turn. Example:
?- splits([1,2,3],S).
S = [1]/[2, 3] ;
S = [1, 2]/[3] ;
false.
Note that Split is not an atom. It is a structure with the functor /. Observe:
?- splits([1,2,3], A/B).
A = [1],
B = [2, 3] ;
A = [1, 2],
B = [3] ;
false.
Here are additional examples. Note that splitting a list with less than two elements fails.
?- splits([],S).
false.

?- splits([1],S).
false.

?- splits([1,2],S).
S = [1]/[2] ;
false.

?- atom_chars('splits',Chars), splits(Chars,S).
Chars = [s, p, l, i, t, s],
S = [s]/[p, l, i, t, s] ;
Chars = [s, p, l, i, t, s],
S = [s, p]/[l, i, t, s] ;
Chars = [s, p, l, i, t, s],
S = [s, p, l]/[i, t, s] ;
Chars = [s, p, l, i, t, s],
S = [s, p, l, i]/[t, s] ;
Chars = [s, p, l, i, t, s],
S = [s, p, l, i, t]/[s] ;
false.
My solution uses only two predicates: append and \==.

Problem 3. (6 points) repl.pl

Write a predicate repl(?E, +N, ?R) that unifies R with a list that is N replications of E. If N is less than 0, repl fails.
?- repl(x,5,L).
L = [x, x, x, x, x].

?- repl(1,3,[1,1,1]).
true.

?- repl(X,2,L), X=7.
X = 7,
L = [7, 7].

?- repl(a,0,X).
X = [].

?- repl(a,-1,X).
false.

My solution does not use findall. If you do use findall, you may encounter the problem described on slide 181.

Problem 4. (6 points) pick.pl

Write a predicate pick(+From, +Positions, -Picked) that unifies Picked with an atom consisting of the characters in From at the zero-based, non-negative positions in Positions.
?- pick('testing', [0,6], S).
S = tg.

?- pick('testing', [1,1,1], S).
S = eee.

?- pick('testing', [10,2,4], S).
S = si.

?- between(0,6,P), P2 is P+1, pick('testing', [P,P2], S),
   writeln(S), fail.
te
es
st
ti
in
ng
g
false.

?- pick('testing', [], S).
S = ''.
If a position is out of bounds, it is silently ignored. My solution uses atom_chars, findall, member, and nth0.

Problem 5. (6 points) polyperim.pl

Write a predicate polyperim(+Vertices, -Perim) that unifies Perim with the perimeter of the polygon described by the sequence of Cartesian points in Vertices, a list of pt structures.

?- polyperim([pt(0,0),pt(3,4),pt(0,4),pt(0,0)],Perim).
Perim = 12.0.

?- polyperim([pt(0,0),pt(0,1),pt(1,1),pt(1,0),pt(0,0)],Perim).
Perim = 4.0.

?- polyperim([pt(0,0),pt(1,1),pt(0,1),pt(1,0),pt(0,0)],Perim).
Perim = 4.82842712474619.
There is no upper bound on the number of points but at least four points are required, so that the minimal path describes a triangle. (Think of it as ABCA, with the final A "closing" the path.) If less than four points are specified, polyperim fails with a message:
?- polyperim([pt(0,0),pt(3,4),pt(0,4)],Perim).
At least a four-point path is required.
false.
The last point must be the same as the first. If not, polyperim fails with a message:
?- polyperim([pt(0,0),pt(3,4),pt(0,4),pt(0,1)],Perim).
Path is not closed.
false.
Note: check first for the minimum number of points and then a closed path. This is not a course on geometric algorithms so keep things simple! Calculate the perimeter by simply summing the lengths of all the sides; don't worry about intersecting sides, coincident vertices, etc.

Be sure that polyperim produces only one result.

Problem 6. (3 points) rotate.pl

Write a Prolog predicate rotate(+L,?R) that instantiates R to each unique list that is a left rotation of L.

For example, the list [1,2,3] can be rotated left to produce [2,3,1] which in turn can be rotated left again to produce [3,1,2].

?- rotate([1,2,3],L), writeln(L), fail.
[1,2,3]
[2,3,1]
[3,1,2]
false.

?- rotate([a,b,c,d],R).
R = [a, b, c, d] ;
R = [b, c, d, a] ;
R = [c, d, a, b] ;
R = [d, a, b, c] ;
false.

?- rotate([1], R).
R = [1] ;
false.

?- rotate([], R).
false.
Additionally, rotate can be asked whether the second term is a rotation of the first term:
?- rotate([a,b,c],[c,a,b]).
true ;
false.

?- rotate([a,b,c],[c,b,a]).
false.

Problem 7. (6 points) outin.pl

Write a Prolog predicate outin(+L, ?R) that generates the elements of the list L in an "outside-in" sequence: the first element, the last element, the second element, the next to last element, etc. If the list has an odd number of elements, the middle element is the last one generated.

Restriction: You may not use is/2.

?- outin([1,2,3,4,5],X).
X = 1 ;
X = 5 ;
X = 2 ;
X = 4 ;
X = 3 ;
false.

?- outin([1,2,3,4],X).
X = 1 ;
X = 4 ;
X = 2 ;
X = 3 ;
false.

?- outin([1],X).
X = 1 ;
false.

?- outin([],X).
false.

Problem 8. (6 points) btw.pl

Write a Prolog predicate btw(+L, +X, ?R) that instantiates R to copies of L with X inserted between each element in turn.

Restriction: You may not use append or between.

?- btw([1,2,3,4,5],---,R).
R = [1, ---, 2, 3, 4, 5] ;
R = [1, 2, ---, 3, 4, 5] ;
R = [1, 2, 3, ---, 4, 5] ;
R = [1, 2, 3, 4, ---, 5] ;
false.

?- btw([1,2],***,R).
R = [1, ***, 2] ;
false.

?- btw([1],***,R).
false.

?- btw([],x,R).
false.

Problem 9. (12 points) fsort.pl

Imagine that you have a stack of pancakes of varying diameters that is represented by a list of integers. The list [3,1,5] represents a stack of three pancakes with diameters of 3", 1" and 5" where the 3" pancake is on the top and the 5" pancake is on the bottom. If a spatula is inserted below the 1" pancake (putting the stack [3,1] on the spatula) and then flipped over, the resulting stack is [1,3,5].

In this problem you are to write a predicate fsort(+Pancakes, -Flips) that instantiates Flips to a sequence of flip positions that will order Pancakes, an integer list, from smallest to largest, with the largest pancake (integer) on the bottom (at the end of the list). fsort stands for "flip sort".

fsort does not produce a sorted list—its only result is the sequence of flip positions.

The flip position is defined as the number of pancakes on the spatula. In the above example the flip position is 2. Flips would be instantiated to [2].

Below are some examples. Note the use of a set of case/2 facts to show a series of examples with one query.

$ cat a6/fsortcases.pl
case(a, [3,1,5]).
case(b, [5,4,3,2,1]).
case(c, [3,4,5,1,2]).
case(d, [5,1,3,1,4,2]).
case(e, [1,2,3,4]).
case(f, [5]).
case(g, [3,1,3,1,2]). % note duplicate sizes...

$ swipl
...
?- [a6/fsortcases,fsort].
% fsortcases compiled 0.00 sec, 7 clauses
% fsort compiled 0.00 sec, 10 clauses
true.

?- case(_,L), fsort(L,Flips).
L = [3, 1, 5],
Flips = [2] ;

L = [5, 4, 3, 2, 1],
Flips = [5] ;

L = [3, 4, 5, 1, 2],
Flips = [3, 5, 2] ;

L = [5, 1, 3, 1, 4, 2],
Flips = [6, 2, 5, 2, 4, 3] ;

L = [1, 2, 3, 4],
Flips = [] ;

L = [5],
Flips = [] ;

L = [3, 1, 3, 1, 2],
Flips = [5, 3, 4, 2, 3].
Your solution needs only to produce a sequence of flips that results in a sorted stack; the sequences it produces do NOT need to match the sequences shown above. There are some requirements on the flips, however:
  1. All flips must be between 2 and the number of pancakes, inclusive.
  2. There must be no consecutive identical flips, like [5,3,3,4].
  3. fsort must always generate exactly one solution.
You may assume that stacks always have at least one pancake and that pancake sizes are always greater than zero.

"Pancake sorting" is a well-known problem. I first encountered it in 1993's Duke Internet Programming Contest. There's even a Wikipedia article about pancake sorting. (Read it!) I debated whether to go with this problem because it's so well known but it's a fun problem and it's interesting to solve in Prolog, so here it is. I did Google up one "solution" in Prolog but it's got some issues! I strongly encourage you to build your Prolog skills by solving this problem without Google's assistance.

The clauses in my current solution have a total of seventeen goals. I don't use is/2 at all. I do use max_list. You might find nth0 to be useful; if you look at slide 137 closely you'll see it can be used to both extract values and find values, among other things. There's an nth1, too, if you find one-based thinking to be a better choice.

Problem 10. (18 points) connect.pl

In this problem you are to write a predicate connect/4 that finds and displays a suitable sequence of cables to connect two pieces of equipment that are some distance apart. Each cable is specified by a three element list. Here is a list that represents a twelve-foot cable with a male connector on one end and a female connector on the other:

[m,12,f]
Let's consider an example of using connect to produce a sequence of cables. Imagine that to your left is a piece of equipment with a male connector. On your right, fifteen feet away, is a piece of equipment with a female connector. To connect the equipment you have two cables: The following query represents the situation described above.
?- connect([ [m,10,f], [f,7,m] ], m, 15, f).
connect's first argument is a list with the two cables. The second, third, and fourth arguments respectively represent the gender of the connector of the equipment on the left (male—m), the distance between the equipment (15 feet), and the gender of the connector of the equipment on the right (female—f). Here's the query and its result:
?- connect([ [m,10,f], [f,7,m] ], m, 15, f).
F----------MF-------M
true.
We see that a connection is possible in this case; a valid sequence of connections is shown. Observe that the first cable was reversed to make the connection. The number of dashes is the length of the cable. There's some slack in the connection—only fifteen feet needs to be spanned but the total length of the cables is seventeen feet. That's fine.

Note that the output has no representation of the pieces of equipment on the left and right that we're connecting with the cables.

Only male/female connections are valid in the world of connect.pl. In some cases a connection cannot be made, but connect always succeeds:

?- connect([[m,10,f], [f,7,m] ], m, 25, f).
Cannot connect
true.

?- connect([[m,10,f], [f,7,m] ], m, 15, m).
Cannot connect
true.
More examples:
?- connect([[m,1,m],[f,1,f],[m,10,m],[f,5,f],[m,3,f]], m, 20, f).
F-FM-MF-----FM----------MF---M
true.

?- connect([[m,1,m],[f,1,f],[m,10,m],[f,5,f],[m,3,f]], m, 20, m).
Cannot connect
true.

?- connect([[m,1,m],[f,1,f],[m,10,m],[f,5,f],[m,3,f]], m, 10, f).
F-FM-MF-----FM----------M
true.

?- connect([[m,10,f]], m, 1, f).
F----------M
true.
IMPORTANT: The ordering of cables your solution produces for a particular connection need NOT match that shown above. Any valid ordering is suitable. (A Ruby program, a6/pc.rb, analyzes the output.)

Note that you do not need to use all the cables or exactly span the distance.

Assume the following:

You can approach this problem using an approach similar to that in the pit-crossing example, slide 211+.

My current solution is around 25 goals; about a third of those are related to producing the output.

Problem 11. (12 points) iz.pl

In this problem you are to write a predicate iz/2, an analog of is/2 that evaluates expressions involving atoms rather than the arithmetic expressions that is/2 evaluates.

Let's start with some examples:

?- S iz abc+xyz.      % + concatenates two atoms.
S = abcxyz.

?- S iz (ab + cd)*2.  % *N produces N replications of the atom.
S = abcdabcd.

?- S iz -cat*3.       % - is a unary operator that produces a
                             % reversed copy of the atom.
S = tactactac.

?- S iz -cat+dog.
S = tacdog.

?- S iz abcde / 2.    % / N  produces the first N characters
                      % of the atom.
S = ab.

?- S iz abcde / -3.   % If N is negative, / produces last N
                      % characters
S = cde.

?- N is 3-5, S iz (-testing)/N.
N = -2,
S = et.
Two functions, len and wrap, are also supported. len(E) evaluates to an atom (not a number!) that represents the length of E.
?- N iz len(abc*15).
N = '45'.

?- N iz len(len(abc*15)).
N = '2'.
wrap adds characters to both ends of its argument. If wrap is called with two arguments, the second argument is concatenated on both ends of the string:
?- S iz wrap(abc, ==).
S = '==abc=='.

?- S iz wrap(wrap(abc, ==), '*' * 3).
S = '***==abc==***'.
If wrap is called with three arguments, the second and third arguments are concatenated to the left and right ends of the string, respectively:
?- S iz wrap(abc, '(', ')').
S = '(abc)'.

?- S iz wrap(abc, '>' * 2, '<' * 3).
S = '>>abc<<<'.
It is important to understand that len(xy), wrap(abc, ==), and wrap(abc, '(', ')') are simply structures. If iz encounters a two-term structure whose functor is wrap (like wrap(abc, ==)) its value is the concatenation of the second term, the first term, and the second term. iz evaluates len and wrap like is evaluates random and sqrt.

The atoms comma, dollar, dot, and space do not evaluate to themselves with iz/2 but instead evaluate to the atoms ',', '$', '.', and ' ', respectively. (They are similar to e and pi in arithmetic expressions evaluated with is/2.)

In the following examples note that swipl is adding some parentheses on the comma and the dollar sign that stand alone. That adornment disappears when those characters are used in combination with others.

?- S iz comma.
S = (',').

?- S iz dollar.
S = ($).

?- S iz dot.
S = ('.').

?- S iz space.
S = ' '.

?- S iz comma+dollar*2+space+dot*3.
S = ',$$ ...'.

?- S iz wrap(wrap(space+comma+space,dot),dollar).
S = '$. , .$'.

?- S iz dollarcommadotspace.
S = dollarcommadotspace.
The final example above demonstrates that these four special atoms don't have special meaning if they appear in a larger atom.

Here is a summary for iz/2:

-Atom iz +Expr unifies Atom with the result of evaluating Expr, a structure representing a calculation involving atoms. The following operators are supported:
E1 + E2
Concatenates the atoms produced by evaluating E1 and E2 with iz.

E * N
Concatenates E (evaluated with iz) with itself N times. (Just like Ruby.) N is a term that can be evaluated with is/2 (repeat, is/2). Assume N >= 0.

E / N
Produces the first (last) N characters of E if N is greater than (less than) 0. If N is zero, an empty atom is produced. (An empty atom is shown as two single quotes with nothing between them.) N is a term that can be evaluated with is/2. The behavior is undefined if abs(N) is greater than the length of E.

-E
Produces E reversed.

len(E)
Produces an atom, not a number, that represents the length of E.

wrap(E1,E2)
Produces E2+E1+E2.

wrap(E1,E2,E3)
Produces E2+E1+E3. The behavior of iz is undefined for all cases not covered by the above. Things like 1+2, abc*xyz, etc., simply won't be tested.

Here are some cases that demonstrate that the right-hand operand of * and / can be an arithmetic expression:

?- X = 2, Y= 3, S iz 'ab' * (X+Y*3).
X = 2,
Y = 3,
S = ababababababababababab .

?- S = '0123456789', R iz S + -S, End iz R / -(2+3).
S = '0123456789',
R = '01234567899876543210',
End = '43210' .

Implementation notes

One of the goals of this problem is to reinforce the idea that for an expression like -a+b*3 Prolog creates a tree structure that reflects the precedence and associativity of the operators. is/2 evaluates a tree as an arithmetic expression. iz/2 evaluates a tree as a "string expression".

Note the contrast when the same tree is evaluated by is and iz:

?- X is pi + e*3.        % using is
X = 11.296438138966929.

?- X iz pi + e*3.        % using iz
X = pieee .
It's important to understand Prolog itself parses the expression and builds a corresponding structure that takes operator precedence into account. display/1 shows the tree:
?- display(pi + e*3).
+(pi,*(e,3))
true.

Processing of syntactically invalid expressions like abc + + xyz never proceeds as far as a call to iz.

Below is some code to get you started. It fully implements the + operation.

$ cat a6/iz0.pl
/*
Declare iz to be an infix operator.  (Remember that the
leading :- causes the code to be evaluated as a goal, not
consulted as a clause.)
*/
:-op(700, xfx, iz).

A iz A :- atom(A), !.
R iz E1+E2 :- R1 iz E1, R2 iz E2, atom_concat(R1, R2, R).
Here are examples that use the version of iz just above.
?- [a6/iz0].     % Note: no ".pl"
true.

?- X iz abc+def.
X = abcdef.

?- X iz abc+def, Y iz X+'...'+X.
X = abcdef,
Y = 'abcdef...abcdef'.

?- X iz a+b+(c+(de+fg)+hij+k)+l.
X = abcdefghijkl.
Let's look at the code provided above and first consider the second clause:
R iz E1 + E2 :- R1 iz E1, R2 iz E2, atom_concat(R1, R2, R).
The first thing you may notice is that the head, R iz E1 + E2, doesn't match the functor(term,term,...) form we've always seen for the heads of rules. That's because the op(700, xfx, iz) call above lets us use iz as an infix operator, and that applies in both the head and body of a rule. Here is a completely equivalent version that doesn't take advantage of the op specification:
iz(R,E1+E2) :- iz(R1,E1), iz(R2,E2), atom_concat(R1, R2, R).
With that equivalence explained, let's focus on the version in a6/iz0.pl, which uses the infix form:
R iz E1 + E2 :- R1 iz E1, R2 iz E2, atom_concat(R1, R2, R).
Consider the goal X iz ab+cd. That goal unifies with the head of the above rule like this:
?- (X iz ab+cd) = (R iz E1+E2).
X = R,
E1 = ab,
E2 = cd.
If E1 is instantiated to ab then the first goal in the body of the rule would be equivalent to R1 iz ab. That goal unifies with the head of this rule:
A iz A :- atom(A), !.
This rule represents the base case for the recursive evaluation performed by iz. It says,
"If A is an atom then the result of evaluating that atom is A."
Another way to read it is,
"An atom evaluates to itself."
The result is that R1 iz ab" instantiates R1 to ab. Note that the leaves of the expression's tree are always atoms.

It's important to recognize that because the iz(R, E1+E2) rule is recursive, it'll handle every tree composed of + operations.

Here are the heads (and necks) for all the iz rules that I've got in my solution:

R iz E1+E2 :-

R iz E1*NumExpr :-

R iz -E :-
    
R iz E1 / NumExpr :-

R iz len(E) :-

R iz wrap(E,Wrap) :-

R iz wrap(E,First,Last) :-
Via recursion, those heads handle all possible combinations of operations, like this one:
?- X iz wrap((-(ab+cde*4)/6+xyz), 'Start>','<'+(end*3+zz*2)).
X = 'Start>edcedcxyz<endendendzzzz'.
If you find yourself wanting to add a bunch of rules like
R iz (E1+E2+E2) :- ...

R iz (E1*E2) / NumExpr :- ...
then STOP! You're not recognizing that a set of rules based on the heads above will cover ALL the operations.

The atomic_list_concat predicate

iz0.pl above uses atom_concat but atomic_list_concat(+List, -Atom) is a more general predicate:
?- atomic_list_concat([ab,c,def,ghij], S).
S = abcdefghij.

A minor parsing problem

In the slides I fail to mention that Prolog requires some sort of separation between operators. Example:
?- X iz abc+-abc.    % No space between + and -
ERROR: Syntax error: Operator expected
ERROR: X iz abc
ERROR: ** here **
ERROR: +-abc .
To make it work, add a space or parenthesize:
?- X iz abc+ -abc.
X = abccba.

?- X iz abc+(-abc).
X = abccba.
This issue only arises with unary operators, of course.

Problem 12. (5 points of Extra Credit) mishaps.pl

The following logic puzzle, "Rural Mishaps", was written by Margaret Shoop. It was published in The Dell Book of Logic Problems #2.

"A butt by the family cow was one of the five different mishaps that befell Farmer Brown, his wife, his daughter, his teenage son, and his farmhand one summer morning. From the rhyme that follows, can you determine the mishap that happened to each of the five, and the order in which the events occurred?

"The garter snake was surprised in a patch And bit a grown man's finger. One person who weeded a flower bed Received a nasty stinger. The farmer's mishap happened first; Son Johnny's happened third. When Mr. Reston was kicked by the mule, He said, "My word! My word!" The sting of the bee was the fourth mishap To befall our rural cast. Neither it nor the wasp attacked Mrs. Brown Whose mishap wasn't the last."

For mishaps.pl you are to encode as Prolog goals the pertinent information in the above rhyme and then write a predicate mishaps/0 that uses those goals to solve the puzzle.

a6/mishaps-out.txt shows a run of mishaps/0 with the exact output you are to produce, but you might enjoy the challenge of solving the puzzle using Prolog before looking at the expected output or trying the tester.

The challenge of this problem is of course the encoding of the information as Prolog goals. Solutions must both produce the correct output and accurately encode the information as stated in the rhyme to earn full credit. The tester will check for correct output; we'll check manually for accurate encoding.

Implementation notes

Obviously, this problem is in the style of The Zebra Puzzle, on slide 233+. The code for the Zebra Puzzle establishes a number of constraints for the list Houses. In this problem you'll want to establish constraints for a list of mishaps instead of a list of houses.

You might start like this:

mishaps(Mishaps) :- Mishaps = [ ... ].
A similar start for the Zebra puzzle is this:
zebra(Houses) :-
    Houses = [house(norwegian, _, _, _, _), _, 
              house(_, _, _, milk, _), _, _].
Querying zebra(H) produces only one possible value for H, the list of houses:
?- zebra(H).
H = [house(norwegian, _G1222, _G1223, _G1224, _G1225),
    _G1227,
    house(_G1233, _G1234, _G1235, milk, _G1237),
    _G1239,
    _G1242].
Let's add a member goal that encodes the statement that the Englishman lives in the red house:
zebra(Houses) :-
    Houses = [house(norwegian, _, _, _, _), _,
              house(_, _, _, milk, _), _, _],
    member(house(englishman, _, _, _, red), Houses).
Now we get four possible values for H: (blank lines added)
?- zebra(H).
H = [house(norwegian, _G2194, _G2195, _G2196, _G2197),
     house(englishman, _G2218, _G2219, _G2220, red),
     house(_G2205, _G2206, _G2207, milk, _G2209),
     _G2211,
     _G2214] ;

H = [house(norwegian, _G2194, _G2195, _G2196, _G2197),
     _G2199,
     house(englishman, _G2206, _G2207, milk, red),
     _G2211,
     _G2214] ;

H = [house(norwegian, _G2194, _G2195, _G2196, _G2197),
     _G2199,
     house(_G2205, _G2206, _G2207, milk, _G2209),
     house(englishman, _G2218, _G2219, _G2220, red),
     _G2214] ;

H = [house(norwegian, _G2194, _G2195, _G2196, _G2197),
     _G2199,
     house(_G2205, _G2206, _G2207, milk, _G2209),
     _G2211,
     house(englishman, _G2218, _G2219, _G2220, red)].

?- findall(r, zebra(H), Results), length(Results,N).
Results = [r, r, r, r],
N = 4.
If we add a goal that states that the Spaniard owns the dog, we go up to twelve possible values for H:
zebra(Houses) :-
    Houses = [house(norwegian, _, _, _, _), _,
              house(_, _, _, milk, _), _, _],
    member(house(englishman, _, _, _, red), Houses),
    member(house(spaniard, dog, _, _, _), Houses).

?- findall(r, zebra(H), Results), length(Results,N).
Results = [r, r, r, r, r, r, r, r, r|...],
N = 12.
Some goals will make the number of possible values for the list of houses go up, and other goals will make the number of possible values go down. If we properly encode all the information, we'll end up with only one possible value for the list of houses.

Follow a similar process when adding goals to represent information about the mishaps. That is, add goals to mishaps/1 one at a time. Query mishaps(M) after each addition.

If you inadvertently introduce a contradiction for the Zebra puzzle, like length(Houses,6), you'll see this:

?- zebra(H).
false.
Similarly, if you add a goal to mishaps/1 and find that mishaps(M) then fails, you'll need to step back and consider why that new goal creates a situation with no possible solutions. You might try leaving the new goal in place and commenting one or more earlier goals to find the conflict.

When you've got mishaps/1 working—producing a single possibility for the list of mishaps—use it to write mishaps/0.

Remember: Solutions must both produce the correct output and accurately encode the information as stated in the rhyme to earn full credit. The tester will check for correct output; we'll check manually for accurate encoding. We'll be happy to take a look at your code prior to the deadline to see if we see any issues with the encoding.

Problem 13. Extra Credit observations.txt

Submit a plain text file named observations.txt with...

(a) (1 point extra credit) An estimate of how many hours it took you to complete this assignment. Put that estimate on a line by itself, like this:

Hours: 9.5
There should be only one "Hours:" line in observations.txt. (It's fine if you care to provide per-problem times, and that data is useful to us, but report it in some form of your own invention that doesn't contain the string "Hours:". Thanks!)

Feedback and comments about the assignment are welcome, too. Was it too long, too hard, too detailed? Speak up! I appreciate all feedback, favorable or not.

(b) (1-3 points extra credit) Cite an interesting course-related observation (or observations) that you made while working on the assignment. The observation should have at least a little bit of depth. Think of me thinking "Good!" as one point, "Excellent!" as two points, and "Wow!" as three points. I'm looking for quality, not quantity.

Turning in your work

Use a6/turnin to submit your work. You can run a6/turnin as often as you want. We'll grade your final pre-deadline submission.

Just like on assignment 5 I'll use my plsize script to show you the "sizes" of my solutions. (Recall that the script counts left parentheses and commas, which I claim is a reasonable proxy for program size for Prolog source code.)

Here's what I see as of press time, with comments stripped:

$ a6/plsize $(grep -v txt a6/delivs)
append.pl: 65
splits.pl: 7
repl.pl: 15
pick.pl: 19
polyperim.pl: 53
rotate.pl: 10
outin.pl: 9
btw.pl: 13
fsort.pl: 54
connect.pl: 100
iz.pl: 76
mishaps.pl: 77

Miscellaneous

Aside from -> and ; you can use any elements of Prolog that you desire, but the assignment is written with the intention that, aside from the extra-credit problem mishaps.pl, it can be completed easily using only the material presented on Prolog slides 1-224.

As of press time I don't know whether we'll study the brick laying puzzle, slides 226-232, but it is another example of a problem like pit-crossing and connect.pl.

The extra credit problem mishaps.pl is in the style of the Zebra Puzzle, slide 224-231.

Point values of problems correspond closely to the "assignment points" mentioned in the syllabus. For example, a 10-point problem would correspond to about 1% of your final grade in the course.

Feel free to use comments as you see fit, but no comments are required in your code.

In Prolog, % is comment to end of line. Multi-line comments with /* ... */, just like in Java, are supported, too.

Remember that late assignments are not accepted and that there are no late days; but if circumstances beyond your control interfere with your work on this assignment, there may be grounds for an extension. See the syllabus for details.

My estimate is that it will take a typical CS junior 10-14 hours to complete this assignment.

Our goal is that everybody gets 100% on this assignment AND gets it done in an amount of time that is reasonable for them.

Assignments are not take-home tests! We hope you'll make use of Piazza, email, Discord and office hours if problems arise. If you're getting toward the hours I estimate above and don't seem to be close to completing it, or you're simply worried about your progress, email us! Give us a chance to speed you up!