How to attach properties to terms? - prolog

I want to attach properties to my terms, from a set of about 50 different properties. Usually only a small subset of them are used for a given term. There are many ways to represent these properties, but I am not satisfied with any of them.
For the sake of discussion, here is a set of properties and their possible values:
hair: bald, blonde, brune, red
eyes: blue, green, brown
first_name: John, Dick, Harry
There are many ways to represent these properties, for example with a list of pairs:
[eyes-blue, hair-blonde]
The only representation that seems to work is to use a very long list, where each index is used for a specific property:
?- T1=[blonde,_,_], T2=[_,blue,_], T1=T2.
T1 = T2, T2 = [blonde, blue, _1266]
?- T1=[X,_,_], X=blue.
T1 = [blue, _1230, _1236],
X = blue
But it's unreadable with 50 properties, and very bugprone (in my case, a whole set of predicates is dedicated to each property, and sometimes to each value of a property).
The way I would use such a feature would be by having conditions like "Terms T1 and T2 have the same value for property X", or "Terms T1 and T2 are the same", where T1 and T2 have attributes which can be set elsewhere, or can be left unset.
Using dicts desn't work, because unset keys are considered non-existent:
?- T1 = _{eyes:blue, hair:blonde}, T2 = _{eyes:blue}, T1 = T2.
false.
For this to work, I would need to initialize each term with the 50 (mostly irrelevant) properties with free variables, on the off-chance that some of them will be used.
What other options do I have? I am open to using a different logic programming language if there is something closer to my needs than prolog.

With the "very long list", you have indeed found one possible representation that lets you directly use Prolog's built-in unification to perform the task for you.
As you note, this comes at a price though: It's unreadable, error-prone, wasteful etc.
There are many possible ways to solve the task, and I would like to give you two pointers that I hope you find relevant for your task.
Option 1: Use lists of pairs
This is in fact already mentioned in your post. Pairs of the form hair-blonde etc. are a natural way to represent the available data. By convention, (-)/2 is frequently used to denote pairs in Prolog.
All that is missing is precisely describing what "merging" such pairs means. You call it "unification", so let us use this terminology although it is of course different from syntactic unification that is available with (=)/2. One way to define the relation we want is:
unify_pairs([], APs, APs).
unify_pairs([A1-P1|APs1], APs2, APs) :-
if_(selectd_t(A1-P1, APs2, APs2Rest),
APs=[A1-P1|Rest],
if_(attr_exists_t(A1, APs2),
false,
APs = [A1-P1|Rest])),
unify_pairs(APs1, APs2Rest, Rest).
attr_exists_t(A, APs, T) :-
pairs_keys(APs, As),
memberd_t(A, As, T).
selectd_t(E, Xs0, Xs, T) :-
i_selectd_t(Xs0, Xs, E, T).
i_selectd_t([], [], _, false).
i_selectd_t([X|Xs], Rest, E, T) :-
if_(X=E, (T=true,Rest=Xs), (Rest = [X|Rs],i_selectd_t(Xs, Rs, E, T))).
This uses library(reif) and two auxiliary predicates to distinguish the different cases.
Your test cases work as required. For example:
?- unify_pairs([hair-blonde], [eyes-blue], Ps).
Ps = [hair-blonde, eyes-blue].
?- unify_pairs([eyes-blue], [eyes-brown], Ps).
false.
Importantly, we can use it in all directions, and so we can also post significantly more general queries. For example:
?- unify_pairs([T1-P1], [T2-P2], TPs).
T1 = T2,
P1 = P2,
TPs = [T2-P2] ;
TPs = [T1-P1, T2-P2],
dif(T2, T1),
dif(f(T2, P2), f(T1, P1)).
Such answers help us to obtain a better understanding of the relation, and to test it more exhaustively.
Option 2: Use lists of pairs again
The second pointer I would like to include is found in library(ordsets) and similar libraries that ship with several Prolog systems.
This again lets you use lists, even lists of pairs. Importantly, lists are available in all Prolog systems. Various operations are quite efficient due to the way these libraries represent sets as ordered lists.
However, the price you may pay in such cases is the generality explained in the first approach. I suggest you first try the more general approach (i.e., Option 1), and then, only if necessary, resort to lower-level approaches that are more error-prone and less general.

You maybe say "unification" but you mean something different from what unification normally means in Prolog which is why your question might be mistaken for a different question. You could do some things with SWI-Prolog dicts:
?- _{hair:blonde, eyes:blue} >:< _{eyes:blue}.
true.
?- _{hair:blonde, eyes:blue} >:< _{eyes:blue, hair:Color}.
Color = blonde.
?- _{hair:blonde, eyes:blue} >:< _{eyes:blue, hair:bald}.
false.
but you cannot directly do what you need, because if you "put" into a dict you add or replace which is not what you want.
?- R =_{eyes:blue}.put(_{hair:blonde}).
R = _7436{eyes:blue, hair:blonde}.
(this one was OK)
?- R =_{eyes:blue}.put(_{eyes:brown}).
R = _7436{eyes:brown}.
(this is not what you want, is it?)
what you want I don't know what to call in words but it is some form of finding union on keys in key-value pairs. But you can just do it with dicts I think if you first do P1 >:< P2 and then put_dict(P1, P2, Result)?
?- P1 = _{eyes:blue},
P2 = _{hair:blonde,eyes:brown},
P1 >:< P2, put_dict(P1, P2, Result).
false.
?- P1 = _{eyes:blue},
P2 = _{hair:blonde},
P1 >:< P2, put_dict(P1, P2, Result).
Result = _10044{eyes:blue, hair:blonde}.
?- P1 = _{eyes:blue},
P2 = _{hair:blonde,eyes:blue},
P1 >:< P2, put_dict(P1, P2, Result).
Result = _10046{eyes:blue, hair:blonde}.
Please respond if this is what you were asking because I am really not sure? But what is even more important actually is that you think a bit more carefully about the real problem you are trying to model because maybe? (just maybe?) you are thinking of it in terms of solution that is not as good as another solution that will make the problem be a lesser problem or a problem with already existing better solutions. Maybe it will help if you provide even more context about your problem in your question, because now there is enough context about how you tried to solve it but I don't know what you are really solving.

You could make the attributes one-arity terms, like this:
hair(bald)
hair(blonde)
eyes(blue)
eyes(green)
...
That would rule out unifications like
hair(blonde) = hair(red)
and you could quite easily write your own predicate for combining two lists, which could also block/filter out multiple instances of the same attribute.
In languages with strong typing this is a nice representation, but I'm not sure it's so useful in Prolog. Anyway it is a possibility.

I think I understand your question but I don't think I understand your difficulty. You could achieve what you want with dicts, with assocs, with lists of pairs.... You say:
Terms T1 and T2 have the same value for property X
Here it is with dicts, like the answer by #User9213:
?- _{a:1, foo:2, bar:3}.a = _{a:2, foo:22, baz:33}.a.
false.
?- _{a:1, foo:2, bar:3}.a = _{a:1, foo:22, baz:33}.a.
true.
In other words, to compare a "property" of two dicts, you just say Dict1.X = Dict2.X. Note that this also works with X a variable:
?- X = a, _{a:1, b:2}.X = _{a:1, b:432432}.X.
X = a.
The same would work with any other option already mentioned: with library(assoc) (just get the values for that key and compare), or even for lists of pairs (just do member(Key-Value, List) and compare values).
Then, you also say,
Terms T1 and T2 are the same
Now you really can just compare dicts. For assocs, I am not certain if two assocs are always the same if they have the same contents, but you can make lists and compare those. And if you keep your lists of pairs sorted on keys, you can just compare, as with dicts.
Finally, you say:
where T1 and T2 have attributes which can be set elsewhere, or can be left unset.
This is ambiguous. If an attribute is unset, just leave it out of the dict/assoc/list. "Set elsewhere" I really don't get.
You need to write some code down and get a feel for how things could be done. Showing your difficulties with a code example will help you get specific and useful answers.

Related

Easier way to get "unique" bindings?

Sorry if my terminology is off. Long term (40 years? ouch...) imperative programmer, dabbled in functional, spending some time this morning trying to be a bit more serious about declarative. Going through a learning site, and decided to try the "crossword" in exercise 2.4 here: http://www.learnprolognow.org/lpnpage.php?pagetype=html&pageid=lpn-htmlse7
I've got it, but it feels ridiculously clunky. Here's my newbie solution:
word(astante, a,s,t,a,n,t,e).
word(astoria, a,s,t,o,r,i,a).
word(baratto, b,a,r,a,t,t,o).
word(cobalto, c,o,b,a,l,t,o).
word(pistola, p,i,s,t,o,l,a).
word(statale, s,t,a,t,a,l,e).
crossword(V1,V2,V3,H1,H2,H3):-
word(V1,V1a,V1b,V1c,V1d,V1e,V1f,V1g),
word(V2,V2a,V2b,V2c,V2d,V2e,V2f,V2g),
word(V3,V3a,V3b,V3c,V3d,V3e,V3f,V3g),
word(H1,H1a,H1b,H1c,H1d,H1e,H1f,H1g),
word(H2,H2a,H2b,H2c,H2d,H2e,H2f,H2g),
word(H3,H3a,H3b,H3c,H3d,H3e,H3f,H3g),
V1b = H1b,
V1d = H2b,
V1f = H3b,
V2b = H1d,
V2d = H2d,
V2f = H3d,
V3b = H1f,
V3d = H2f,
V3f = H3f,
not(V1 = V2),
not(V1 = V3),
not(V1 = H1),
not(V1 = H2),
not(V1 = H3),
not(V2 = V3),
not(V2 = H1),
not(V2 = H2),
not(V2 = H3),
not(V3 = H1),
not(V3 = H2),
not(V3 = H3),
not(H1 = H2),
not(H1 = H3),
not(H2 = H3).
It works. crossword will give me the two possible layouts (puzzle is symmetric, after all). But yeesh...
Some of the clunkiness is just because I've only started, so I don't have any feel for how to mark bindings as "don't care" (the 1st, 3rd, 5th, and 7th letters of the words are completely irrelevant, for instance). But what is really chafing me right now is having to put in the triangular matrix of "don't duplicate any bindings" there at the end. This issue keeps coming up (an earlier toy problem involved loves(A,B) and jealous(X,Y) and if you allow X=Y then everybody leading off a loves relationship is claimed to be jealous of themselves (which I see someone else was fighting with a few years ago:Get unique results with Prolog)), but this tutorial doesn't address it. It hasn't even told me about 'not' yet -- I had to dig around elsewhere to get that, which led into completely valid questions of "well, what kind of 'not equal' did you want?", which I am currently unprepared to answer. But I digress...
It is inconceivable to me that this is the way this actually gets done in real code. Combinatorially, it's ridiculous. And it seems like it violates (or at least bends) the principal of least astonishment. Without the uniqueness restrictions, there are a huge number of solutions that just set V1=H1, V2=H2, V3=H3. I guess I could have only disallowed those, but the real solution needs to do the full restriction.
Yes, I completely understand that logically and mathematically there is no reason not to bind the same value into multiple parameters, and also that there are many situations where such a multiple binding is not just helpful but required to handle the issues at hand. I'm not arguing with the default behavior at all, just looking for a better way to express uniqueness constraints when I need them.
I'd love to know a better way to handle this, because honestly I don't think I can dig much deeper into these tutorials if they're all going to require this much fluff to do something so seemingly obvious.
Thanks in advance!
In my opinion, the exercise is setting you up for failure.
First, because it uses a knowledge representation that is unsuitable for processing similar elements in a uniform fashion.
Second, because you do not have the necessary prerequisites at this point in the book to do so, even if the knowledge representation would make it easier.
I can assure you: What you are doing is of course not necessary when programming in Prolog.
So, don't let a single book detract you from the language.
At this point, I would like to show you how you could solve this task if you had more experience with the language, and used more suitable language features. You may enjoy going back to this later, when you have read other material.
The key change I would like to make is to let you reason about the available words more explicitly, as data structures that are available within your program, instead of "only" as facts:
words(Ws) :-
Ws = [[a,s,t,a,n,t,e],
[a,s,t,o,r,i,a],
[b,a,r,a,t,t,o],
[c,o,b,a,l,t,o],
[p,i,s,t,o,l,a],
[s,t,a,t,a,l,e]].
You can of course easily obtain such an explicit (sometimes called spatial) representation automatically, using all-solutions predicates such as findall/3.
The key predicate I now introduce lets us relate a word in this representation to its every second letter:
word_evens([_,A,_,B,_,C,_], [A,B,C]).
Note how easily this relation can be expressed if you can reason explicitly about the list of letters that constitute a word.
Now, the whole solution, using the predicates permutation/2 and transpose/2, which you can either find as library predicates in your Prolog system, or also implement easily yourself:
solution(Ls) :-
Ls = [V1,V2,V3,H1,H2,H3],
words(Ws),
Ws = [First|_],
maplist(same_length(First), Ls),
maplist(word_evens, [H1,H2,H3], Ess),
transpose(Ess, TEss),
maplist(word_evens, [V1,V2,V3], TEss),
permutation(Ws, Ls).
Sample query and the two solutions:
?- solution(Ls).
Ls = [[a, s, t, a, n, t, e], [c, o, b, a, l, t, o], [p, i, s, t, o, l|...], [a, s, t, o, r|...], [b, a, r, a|...], [s, t, a|...]] ;
Ls = [[a, s, t, o, r, i, a], [b, a, r, a, t, t, o], [s, t, a, t, a, l|...], [a, s, t, a, n|...], [c, o, b, a|...], [p, i, s|...]] ;
false.
At least maplist/2 should be available in your Prolog, and same_length/2 is easy to define if your system does not provide it.
If you really want to express disequality of terms, use prolog-dif.
But what is really chafing me right now is having to put in the triangular matrix of "don't duplicate any bindings" there at the end.
We can get a better solution with the all_dif/1 predicate from here: https://stackoverflow.com/a/47294595/4391743
all_dif([]).
all_dif([E|Es]) :-
maplist(dif(E), Es),
all_dif(Es).
This predicate accepts a list of elements that are all different from each other. Don't worry about not understanding it just yet, you can treat it as a black box for now.
You can use this to replace the big block of not goals at the end of your predicate definition:
crossword(V1,V2,V3,H1,H2,H3):-
... % unchanged code here
all_dif([V1, V2, V3, H1, H2, H3]).
With this you get back to only the two solutions in which all the words are used.
I don't have any feel for how to mark bindings as "don't care" (the 1st, 3rd, 5th, and 7th letters of the words are completely irrelevant, for instance).
This is indeed a very important issue! And Prolog should warn you about variables you only use once (called "singletons"), because they are a frequent source of bugs:
Singleton variables: [V1a,V1c,V1e,V1g,V2a,V2c,V2e,V2g,V3a,V3c,V3e,V3g,H1a,H1c,H1e,H1g,H2a,H2c,H2e,H2g,H3a,H3c,H3e,H3g]
You explicitly mark a variable as "don't care" by giving it a name that starts with the underscore character _, or just naming it _ altogether. Different occurrences of _ mark different "don't care" variables. So we get:
crossword(V1,V2,V3,H1,H2,H3):-
word(V1,_,V1b,_,V1d,_,V1f,_),
word(V2,_,V2b,_,V2d,_,V2f,_),
word(V3,_,V3b,_,V3d,_,V3f,_),
word(H1,_,H1b,_,H1d,_,H1f,_),
word(H2,_,H2b,_,H2d,_,H2f,_),
word(H3,_,H3b,_,H3d,_,H3f,_),
V1b = H1b,
V1d = H2b,
V1f = H3b,
V2b = H1d,
V2d = H2d,
V2f = H3d,
V3b = H1f,
V3d = H2f,
V3f = H3f,
all_dif([V1, V2, V3, H1, H2, H3]).
The warnings are gone and we the program is easier to read because the underscores leave "holes" in uninteresting places, and we see more clearly which variables matter.
That leaves us with the task of removing all those equations. General Prolog tip: Except maybe sometimes for reasons of clarity, there is never any need to write an equation of the form Var1 = Var2 where both sides are variables. Just use the same name for both variables in the whole clause, and you get the same result!
So let's replace V1b and H1b by the same variable named A, V1d and H2b by the same variable B, etc.:
crossword(V1,V2,V3,H1,H2,H3):-
word(V1,_,A,_,B,_,C,_),
word(V2,_,D,_,E,_,F,_),
word(V3,_,G,_,H,_,I,_),
word(H1,_,A,_,D,_,G,_),
word(H2,_,B,_,E,_,H,_),
word(H3,_,C,_,F,_,I,_),
all_dif([V1, V2, V3, H1, H2, H3]).
This is equivalent to your initial solution and, I hope, fairly beginner-friendly.
Hopefully this convices you that Prolog programs can be a bit less clunky than your first attempt. Please stick around, we're here to help if you get stuck, and hopefully you will have some less frustrating experiences and see the magic of Prolog.

How to make a list of pairs from facts in SWI-Prolog?

Assuming I have some facts like the following
person(jessica,19,usa).
person(james,18,uk).
person(eric,34,italy).
person(jake,24,france).
how can I create a predicate that creates a large list of pairs of all the names and their corresponding country like so:
?-filter(L).
L=[(jessica,usa),(james,uk),(eric,italy),(jake,france)]
The best solution is this one:
?- bagof((P,C), Age^person(P,Age,C), People).
People = [(jessica, usa), (james, uk), (eric, italy), (jake, france)].
This gives you the same result as findall/3, because findall/3 implicitly assumes existential quantification on all variables not present in the template ((P,C) is the template). In your case you only have one, the age variable. Notice what happens if you don't include that:
?- bagof((P,C), person(P,_,C), People).
People = [(james, uk)] ;
People = [(jessica, usa)] ;
People = [(jake, france)] ;
People = [(eric, italy)].
What happened here? The value of the second parameter was the same across each solution because we didn't inform bagof/3 that we didn't care what it was bound to or even if it was bound to just one thing. This property of bagof/3 and setof/3 (but not findall/3) sometimes turns out to be surprisingly useful, so I tend to prefer using bagof/3 over findall/3 if I only need to mark a variable or two.
It's more obvious if we add another person the same age to the database:
person(janet,18,australia).
?- bagof((P,C), person(P,Age,C), People).
Age = 18,
People = [(james, uk), (janet, australia)] .
?- bagof((P,C), person(P,_,C), People).
People = [(james, uk), (janet, australia)] ;
Assuming person/3 is ground and terminates, you can implement it without setof as:
notin(_, []).
notin(X, [Y|Ys]) :-
dif(X,Y),
notin(X,Ys).
lt_list(_, []).
lt_list(X, [Y|Ys]) :-
X #< Y,
lt_list(X,Ys).
f( [ Name-Location | Rest], Acc) :-
person(Name, _, Location),
lt_list( Name-Location, Acc ),
f(Rest, [Name-Location | Acc]).
f( [], Acc) :-
\+ (person(Name,_,Location), notin(Name-Location,Acc)).
When we query f, we get our solutions:
?- f(Xs,[]).
Xs = [jessica-usa, james-uk, jake-france, eric-italy] ;
false.
I used X-Y instead of (X,Y) for better readability. The predicate notin describes an element that is not contained in a list and lt_list describes an element that is smaller than anything in the list by the standard term order.
The idea is that the first rule generates persons that I have not seen yet. Using the term order makes sure that we don't generate all permutations of the list (try replacing lt_list by notin to see what happens). The second rule makes sure we only terminate if there are no more solutions to generate. Be aware that the rule contains negation, which can have some unwanted side-effects. Most of them are filtered out by only looking at ground terms, but I have not thought well, how bad the impact is in this solution.

Prolog - subsitution and evaluation

Hello good people of programming .
Logic programming is always fascinating compare to imperative programming.
As pursuing unknown of logic programming, there is some problems encountering arithmetic expressions.
Here is the code I have done so far.
number_atom(N) :-
(number(N) -> functor(N, _, _); functor(N, _, _), atom(N)).
arithmeticAdd_expression(V,V,Val,Val).
arithmeticAdd_expression(N, _Var, _Val, N) :-
number_atom(N).
arithmeticAdd_expression(X+Y, Var, Val, R) :-
arithmeticAdd_expression(X, Var, Val, RX),
arithmeticAdd_expression(Y, Var, Val, RY),
(number(RX), number(RY) -> R is RX + RY; R = RX + RY).
Taking add operation as example:
arithmeticAdd_expression(Expression, Variable, Value, Result)
?- arithmeticAdd_expression(a+10, a, 1, Result).
?- Result = 11;
?- Result = a + 10.
?- arithmeticAdd_expression(a+10, b, 1, Result).
?- Result = a + 10.
What I would like to achieve is that
if the atom(s) in the Expression can only be substituted by given Variable and value, then Result is the number only like the example shown above(Result = 11). Else, the Result is the Expression itself only. My problem with the code is somewhere there, I just could figure it out. So, Please someone can help me? Thank you.
An important attraction of logic programming over, say, functional programming is that you can often use the same code in multiple directions.
This means that you can ask not only for a particular result if the inputs are given, but also ask how solutions look like in general.
However, for this to work, you have to put some thought into the way you represent your data. For example, in your case, any term in your expression that is still a logical variable may denote either a given number or an atom that should be interpreted differently than a plain number or an addition of two other terms. This is called a defaulty representation because you have to decide what a variable should denote by default, and there is no way to restrict its meaning to only one of the possible cases.
Therefore, I suggest first of all to change the representation so that you can symbolically distinguish the two cases. For example, to represent expressions in your case, let us adopt the convention that:
atoms are denoted by the wrapper a/1
numbers are denoted by the wrapper n/1.
and as is already the case, (+)/2 shall denote addition of two expressions.
So, a defaulty term like b+10 shall now be written as: a(b)+n(10). Note the use of the wrappers a/1 and n/1 to make clear which case we are dealing with. Such a representation is called clean. The wrappers are arbitrarily (though mnemonically) chosen, and we could have used completely different wrappers such as atom/1 and number/1, or atm/1 and nmb/1. The key property is only that we can now symbolically distinguish different cases by virtue of their outermost functor and arity.
Now the key advantage: Using such a convention, we can write for example: a(X)+n(Y). This is a generalization of the earlier term. However, it carries a lot more information than only X+Y, because in the latter case, we have lost track of what these variables stand for, while in the former case, this distinction is still available.
Now, assuming that this convention is used in expressions, it becomes straight-forward to describe the different cases:
expression_result(n(N), _, _, n(N)).
expression_result(a(A), A, N, n(N)).
expression_result(a(A), Var, _, a(A)) :-
dif(A, Var).
expression_result(X+Y, Var, Val, R) :-
expression_result(X, Var, Val, RX),
expression_result(Y, Var, Val, RY),
addition(RX, RY, R).
addition(n(X), n(Y), n(Z)) :- Z #= X + Y.
addition(a(X), Y, a(X)+Y).
addition(X, a(Y), X+a(Y)).
Note that we can now use pattern matching to distinguish the cases. No more if-then-elses, and no more atom/1 or number/1 tests are necessary.
Your test cases work as expected:
?- expression_result(a(a)+n(10), a, 1, Result).
Result = n(11) ;
false.
?- expression_result(a(a)+n(10), b, 1, Result).
Result = a(a)+n(10) ;
false.
And now the key advantage: With such a pure program (please see logical-purity for more information), we can also ask "What do results look like in general?"
?- expression_result(Expr, Var, N, R).
Expr = R, R = n(_1174) ;
Expr = a(Var),
R = n(N) ;
Expr = R, R = a(_1698),
dif(_1698, Var) ;
Expr = n(_1852)+n(_1856),
R = n(_1896),
_1852+_1856#=_1896 ;
Expr = n(_2090)+a(Var),
R = n(_2134),
_2090+N#=_2134 .
Here, I have used logical variables for all arguments, and I get quite general answers from this program. This is why I have used clpfd constraints for declarative integer arithmetic.
Thus, your immediate issue can be readily solved by using a clean representation, and using the code above.
Only one very small challenge remains: Maybe you actually want to use a defaulty representation such as c+10 (instead of a(c)+n(10)). The task you are then facing is to convert the defaulty representation to a clean one, for example via a predicate defaulty_clean/2. I leave this as an easy exercise. Once you have a clean representation, you can use the code above without changes.

Counter-intuitive behavior of min_member/2

min_member(-Min, +List)
True when Min is the smallest member in the standard order of terms. Fails if List is empty.
?- min_member(3, [1,2,X]).
X = 3.
The explanation is of course that variables come before all other terms in the standard order of terms, and unification is used. However, the reported solution feels somehow wrong.
How can it be justified? How should I interpret this solution?
EDIT:
One way to prevent min_member/2 from succeeding with this solution is to change the standard library (SWI-Prolog) implementation as follows:
xmin_member(Min, [H|T]) :-
xmin_member_(T, H, Min).
xmin_member_([], Min0, Min) :-
( var(Min0), nonvar(Min)
-> fail
; Min = Min0
).
xmin_member_([H|T], Min0, Min) :-
( H #>= Min0
-> xmin_member_(T, Min0, Min)
; xmin_member_(T, H, Min)
).
The rationale behind failing instead of throwing an instantiation error (what #mat suggests in his answer, if I understood correctly) is that this is a clear question:
"Is 3 the minimum member of [1,2,X], when X is a free variable?"
and the answer to this is (to me at least) a clear "No", rather than "I can't really tell."
This is the same class of behavior as sort/2:
?- sort([A,B,C], [3,1,2]).
A = 3,
B = 1,
C = 2.
And the same tricks apply:
?- min_member(3, [1,2,A,B]).
A = 3.
?- var(B), min_member(3, [1,2,A,B]).
B = 3.
The actual source of confusion is a common problem with general Prolog code. There is no clean, generally accepted classification of the kind of purity or impurity of a Prolog predicate. In a manual, and similarly in the standard, pure and impure built-ins are happily mixed together. For this reason, things are often confused, and talking about what should be the case and what not, often leads to unfruitful discussions.
How can it be justified? How should I interpret this solution?
First, look at the "mode declaration" or "mode indicator":
min_member(-Min, +List)
In the SWI documentation, this describes the way how a programmer shall use this predicate. Thus, the first argument should be uninstantiated (and probably also unaliased within the goal), the second argument should be instantiated to a list of some sort. For all other uses you are on your own. The system assumes that you are able to check that for yourself. Are you really able to do so? I, for my part, have quite some difficulties with this. ISO has a different system which also originates in DEC10.
Further, the implementation tries to be "reasonable" for unspecified cases. In particular, it tries to be steadfast in the first argument. So the minimum is first computed independently of the value of Min. Then, the resulting value is unified with Min. This robustness against misuses comes often at a price. In this case, min_member/2 always has to visit the entire list. No matter if this is useful or not. Consider
?- length(L, 1000000), maplist(=(1),L), min_member(2, L).
Clearly, 2 is not the minimum of L. This could be detected by considering the first element of the list only. Due to the generality of the definition, the entire list has to be visited.
This way of handling output unification is similarly handled in the standard. You can spot those cases when the (otherwise) declarative description (which is the first of a built-in) explicitly refers to unification, like
8.5.4 copy_term/2
8.5.4.1 Description
copy_term(Term_1, Term_2) is true iff Term_2 unifies
with a term T which is a renamed copy (7.1.6.2) of
Term_1.
or
8.4.3 sort/2
8.4.3.1 Description
sort(List, Sorted) is true iff Sorted unifies with
the sorted list of List (7.1.6.5).
Here are those arguments (in brackets) of built-ins that can only be understood as being output arguments. Note that there are many more which effectively are output arguments, but that do not need the process of unification after some operation. Think of 8.5.2 arg/3 (3) or 8.2.1 (=)/2 (2) or (1).
8.5.4 1 copy_term/2 (2),
8.4.2 compare/3 (1),
8.4.3 sort/2 (2),
8.4.4 keysort/2 (2),
8.10.1 findall/3 (3),
8.10.2 bagof/3 (3),
8.10.3 setof/3 (3).
So much for your direct questions, there are some more fundamental problems behind:
Term order
Historically, "standard" term order1 has been defined to permit the definition of setof/3 and sort/2 about 1982. (Prior to it, as in 1978, it was not mentioned in the DEC10 manual user's guide.)
From 1982 on, term order was frequently (erm, ab-) used to implement other orders, particularly, because DEC10 did not offer higher-order predicates directly. call/N was to be invented two years later (1984) ; but needed some more decades to be generally accepted. It is for this reason that Prolog programmers have a somewhat nonchalant attitude towards sorting. Often they intend to sort terms of a certain kind, but prefer to use sort/2 for this purpose — without any additional error checking. A further reason for this was the excellent performance of sort/2 beating various "efficient" libraries in other programming languages decades later (I believe STL had a bug to this end, too). Also the complete magic in the code - I remember one variable was named Omniumgatherum - did not invite copying and modifying the code.
Term order has two problems: variables (which can be further instantiated to invalidate the current ordering) and infinite terms. Both are handled in current implementations without producing an error, but with still undefined results. Yet, programmers assume that everything will work out. Ideally, there would be comparison predicates that produce
instantiation errors for unclear cases like this suggestion. And another error for incomparable infinite terms.
Both SICStus and SWI have min_member/2, but only SICStus has min_member/3 with an additional argument to specify the order employed. So the goal
?- min_member(=<, M, Ms).
behaves more to your expectations, but only for numbers (plus arithmetic expressions).
Footnotes:
1 I quote standard, in standard term order, for this notion existed since about 1982 whereas the standard was published 1995.
Clearly min_member/2 is not a true relation:
?- min_member(X, [X,0]), X = 1.
X = 1.
yet, after simply exchanging the two goals by (highly desirable) commutativity of conjunction, we get:
?- X = 1, min_member(X, [X,0]).
false.
This is clearly quite bad, as you correctly observe.
Constraints are a declarative solution for such problems. In the case of integers, finite domain constraints are a completely declarative solution for such problems.
Without constraints, it is best to throw an instantiation error when we know too little to give a sound answer.
This is a common property of many (all?) predicates that depend on the standard order of terms, while the order between two terms can change after unification. Baseline is the conjunction below, which cannot be reverted either:
?- X #< 2, X = 3.
X = 3.
Most predicates using a -Value annotation for an argument say that pred(Value) is the same
as pred(Var), Value = Var. Here is another example:
?- sort([2,X], [3,2]).
X = 3.
These predicates only represent clean relations if the input is ground. It is too much to demand the input to be ground though because they can be meaningfully used with variables, as long as the user is aware that s/he should not further instantiate any of the ordered terms. In that sense, I disagree with #mat. I do agree that constraints can surely make some of these relations sound.
This is how min_member/2 is implemented:
min_member(Min, [H|T]) :-
min_member_(T, H, Min).
min_member_([], Min, Min).
min_member_([H|T], Min0, Min) :-
( H #>= Min0
-> min_member_(T, Min0, Min)
; min_member_(T, H, Min)
).
So it seems that min_member/2 actually tries to unify Min (the first argument) with the smallest element in List in the standard order of terms.
I hope I am not off-topic with this third answer. I did not edit one of the previous two as I think it's a totally different idea. I was wondering if this undesired behaviour:
?- min_member(X, [A, B]), A = 3, B = 2.
X = A, A = 3,
B = 2.
can be avoided if some conditions can be postponed for the moment when A and B get instantiated.
promise_relation(Rel_2, X, Y):-
call(Rel_2, X, Y),
when(ground(X), call(Rel_2, X, Y)),
when(ground(Y), call(Rel_2, X, Y)).
min_member_1(Min, Lst):-
member(Min, Lst),
maplist(promise_relation(#=<, Min), Lst).
What I want from min_member_1(?Min, ?Lst) is to expresses a relation that says Min will always be lower (in the standard order of terms) than any of the elements in Lst.
?- min_member_1(X, L), L = [_,2,3,4], X = 1.
X = 1,
L = [1, 2, 3, 4] .
If variables get instantiated at a later time, the order in which they get bound becomes important as a comparison between a free variable and an instantiated one might be made.
?- min_member_1(X, [A,B,C]), B is 3, C is 4, A is 1.
X = A, A = 1,
B = 3,
C = 4 ;
false.
?- min_member_1(X, [A,B,C]), A is 1, B is 3, C is 4.
false.
But this can be avoided by unifying all of them in the same goal:
?- min_member_1(X, [A,B,C]), [A, B, C] = [1, 3, 4].
X = A, A = 1,
B = 3,
C = 4 ;
false.
Versions
If the comparisons are intended only for instantiated variables, promise_relation/3 can be changed to check the relation only when both variables get instantiated:
promise_relation(Rel_2, X, Y):-
when((ground(X), ground(Y)), call(Rel_2, X, Y)).
A simple test:
?- L = [_, _, _, _], min_member_1(X, L), L = [3,4,1,2].
L = [3, 4, 1, 2],
X = 1 ;
false.
! Edits were made to improve the initial post thanks to false's comments and suggestions.
I have an observation regarding your xmin_member implementation. It fails on this query:
?- xmin_member(1, [X, 2, 3]).
false.
I tried to include the case when the list might include free variables. So, I came up with this:
ymin_member(Min, Lst):-
member(Min, Lst),
maplist(#=<(Min), Lst).
Of course it's worse in terms of efficiency, but it works on that case:
?- ymin_member(1, [X, 2, 3]).
X = 1 ;
false.
?- ymin_member(X, [X, 2, 3]).
true ;
X = 2 ;
false.

Comparing list element structures to each other in Prolog

I am working through sample questions while studying, using SWI-Prolog. I have reached the last section of this question, where I have to recursively (I hope) compare elements of a list containing 'researcher' structures to determine whether or not the researchers have the same surname, and, if they do, return the Forename and Surname of the group leader for that list.
There is only one list that meets this criteria and it has four members, all with the same surname. However, the correct answer is returned FOUR times. I feel my solution is inelegant and is lacking. Here is the question:
The following Prolog database represents subject teaching teams.
% A research group structure takes the form
% group(Crew, Leader, Assistant_leader).
%
% Crew is a list of researcher structures,
% but excludes the researcher structures for Leader
% and Assistant_leader.
%
% researcher structures take the form
% researcher(Surname, First_name, expertise(Level, Area)).
group([researcher(giles,will,expertise(3,engineering)),
researcher(ford,bertha,expertise(2,computing))],
researcher(mcelvey,bob,expertise(5,biology)),
researcher(pike,michelle,expertise(4,physics))).
group([researcher(davis,owen,expertise(4,mathematics)),
researcher(raleigh,sophie,expertise(4,physics))],
researcher(beattie,katy,expertise(5,engineering)),
researcher(deane,fergus,expertise(4,chemistry))).
group([researcher(hardy,dan,expertise(4,biology))],
researcher(mellon,paul,expertise(4,computing)),
researcher(halls,antonia,expertise(3,physics))).
group([researcher(doone,pat,expertise(2,computing)),
researcher(doone,burt,expertise(5,computing)),
researcher(doone,celia,expertise(4,computing)),
researcher(doone,norma,expertise(2,computing))],
researcher(maine,jack,expertise(3,biology)),
researcher(havilland,olive,expertise(5,chemistry))).
Given this information, write Prolog rules (and any additional predicates required) that can be used to return the following:
the first name and surname of any leader whose crew members number more than one and who all have the same surname. [4 marks]
This is the solution I presently have using recursion, though it's unnecessarily inefficient as for every member of the list, it compares that member to every other member. So, as the correct list is four members long, it returns 'jack maine' four times.
surname(researcher(S,_,_),S).
checkSurname([],Surname):-
Surname==Surname. % base case
checkSurname([Researcher|List],Surname):-
surname(Researcher,SameSurname),
Surname == SameSurname,
checkSurname(List,SameSurname).
q4(Forename,Surname):-
group(Crew,researcher(Surname,Forename,_),_),
length(Crew,Length),
Length > 1,
member(researcher(SameSurname,_,_),Crew),
checkSurname(Crew,SameSurname).
How could I do this without the duplicate results and without redundantly comparing each member to every other member each time? For every approach I've taken I am snagged each time with 'SameSurname' being left as a singleton, hence having to force use of it twice in the q4 predicate.
Current output
13 ?- q4(X,Y).
X = jack,
Y = maine ; x4
A compact and efficient solution:
q4(F, S) :-
group([researcher(First,_,_), researcher(Second,_,_)| Crew], researcher(S, F, _), _),
\+ (member(researcher(Surname, _, _), [researcher(Second,_,_)| Crew]), First \== Surname).
Example call (resulting in a single solution):
?- q4(X,Y).
X = jack,
Y = maine.
You are doing it more complicated than it has to be. Your q4/2 could be even simpler:
q4(First_name, Surname) :-
group(Crew, researcher(Surname, First_name, _E), _A),
length(Crew, Len), Len > 1,
all_same_surname(Crew).
Now you only need to define all_same_surname/1. The idea is simple: take the surname of the first crew member and compare it to the surnames of the rest:
all_same_surname([researcher(Surname, _FN, _E)|Rest]) :-
rest_same_surname(Rest, Surname).
rest_same_surname([], _Surname).
rest_same_surname([researcher(Surname, _FN, _E)|Rest), Surname) :-
rest_same_surname(Rest, Surname).
(Obviously, all_same_surname/1 fails immediately if there are no members of the crew)
This should be it, unless I misunderstood the problem statement.
?- q4(F, S).
F = jack,
S = maine.
How about that?
Note: The solution just takes the most straight-forward approach to answering the question and being easy to write and read. There is a lot of stuff that could be done otherwise. Since there is no reason not to, I used pattern matching and unification in the heads of the predicates, and not comparison in the body or extra predicates for extracting arguments from the compound terms.
P.S. Think about what member/2 does (look up its definition in the library, even), and you will see where all the extra choice points in your solution are coming from.
Boris did answer this question already, but I want to show the most concise solution I could come with. It's just for the educational purposes (promoting findall/3 and maplist/2):
q4(F, S) :-
group(Crew, researcher(S, F, _), _),
findall(Surname, member(researcher(Surname, _, _), Crew), Surnames),
Surnames = [ First, Second | Rest ],
maplist(=(First), [ Second | Rest ]).

Resources