DCG for idiomatic phrase preference - prolog

I have a manually made DCG rule to select idiomatic phrases
over single words. The DCG rule reads as follows:
seq(cons(X,Y), I, O) :- noun(X, I, H), seq(Y, H, O), \+ noun(_, I, O).
seq(X) --> noun(X).
The first clause is manually made, since (:-)/2 is used instead
of (-->)/2. Can I replace this manually made clause by
some clause that uses standard DCG?
Best Regards
P.S.: Here is some test data:
noun(n1) --> ['trojan'].
noun(n2) --> ['horse'].
noun(n3) --> ['trojan', 'horse'].
noun(n4) --> ['war'].
And here are some test cases, the important test case is the first test case, since it does only
deliver n3 and not cons(n1,n2). The behaviour of the first test case is what is especially desired:
?- phrase(seq(X),['trojan','horse']).
X = n3 ;
No
?- phrase(seq(X),['war','horse']).
X = cons(n4,n2) ;
No
?- phrase(seq(X),['trojan','war']).
X = cons(n1,n4) ;
No

(To avoid collisions with other non-terminals I renamed your seq//1 to nounseq//1)
Can I replace this manually made clause by some clause that uses standard DCG?
No, because it is not steadfast and it is STO (details below).
Intended meaning
But let me start with the intended meaning of your program. You say you want to select idiomatic phrases over single words. Is your program really doing this? Or, to put it differently, is your definition really unique? I could now construct a counterexample, but let Prolog do the thinking:
nouns --> [] | noun(_), nouns.
?- length(Ph, N), phrase(nouns,Ph),
dif(X,Y), phrase(nounseq(X),Ph), phrase(nounseq(Y),Ph).
Ph = [trojan,horse,trojan], N = 3, X = cons(n1,cons(n2,n1)), Y = cons(n3,n1)
; ...
; Ph = [trojan,horse,war], N = 3, X = cons(n3,n4), Y = cons(n1,cons(n2,n4))
; ... .
So your definition is ambiguous. What you essentially want (probably) is some kind of rewrite system. But those are rarely defined in a determinate manner. What, if two words overlap like an additional noun(n5) --> [horse, war]. etc.
Conformance
A disclaimer up-front: Currently, the DCG document is still being developed — and comments are very welcome! You find all material in this place. So strictly speaking, there is at the current point in time no notion of conformance for DCG.
Steadfastness
One central property a conforming definition must maintain is the property of steadfastness. So before looking into your definition, I will compare two goals of phrase/3 (running SWI in default mode).
?- Ph = [], phrase(nounseq(cons(n4,n4)),Ph0,Ph).
Ph = [], Ph0 = [war,war]
; false.
?- phrase(nounseq(cons(n4,n4)),Ph0,Ph), Ph = [].
false.
?- phrase(nounseq(cons(n4,n4)),Ph0,Ph).
false.
Moving the goal Ph = [] at the end, removes the only solution. Therefore, your definition is not steadfast. This is due to the way how you handle (\+)/1: The variable O must not occur within the (\+)/1. But on the other hand, if it does not occur within (\+)/1 you can only inspect the beginning of a sentence. And not the entire sentence.
Subject to occurs-check property
But the situation is worse:
?- set_prolog_flag(occurs_check,error).
true.
?- phrase(nounseq(cons(n4,n4)),Ph0,Ph).
ERROR: noun/3: Cannot unify _G968 with [war|_G968]: would create an infinite tree
So your program relies on STO-unifications (subject-to-occurs-check unifications) whose outcome is explicitly undefined in
ISO/IEC 13211-1 Subclause 7.3.3 Subject to occurs-check (STO) and not subject to occurs-check (NSTO)
This is rather due to your intention to define the intersection of two non-terminals. Consider the following way to express it:
:- op( 950, xfx, //\\). % ASCII approximation for ∩ - 2229;INTERSECTION
(NT1 //\\ NT2) -->
call(Xs0^Xs^(phrase(NT1,Xs0,Xs),phrase(NT2,Xs0,Xs))).
% The following is predefined in library(lambda):
^(V0, Goal, V0, V) :-
call(Goal,V).
^(V, Goal, V) :-
call(Goal).
Already with this definition we can get into STO situations:
?- phrase(([a]//\\[a,b]), Ph0,Ph).
ERROR: =/2: Cannot unify _G3449 with [b|_G3449]: would create an infinite tree
In fact, when using rational trees we get:
?- set_prolog_flag(occurs_check,false).
true.
?- phrase(([a]//\\[a,b]), Ph0,Ph).
Ph0 = [a|_S1], % where
_S1 = [b|_S1],
Ph = [b|_S1].
So there is an infinite list which certainly has not much meaning for natural language sentences (except for persons of infinite resource and capacity...).

Related

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.

Computer Reasoning about Prologish Boolos' Curious Inference

Boolo's curious inference has been originally formulated with equations here. It is a recursive definition of a function f and a predicate d via the syntax of N+, the natural numbers without zero, generated from 1 and s(.).
But it can also be formulated with Horn Clauses. The logical content is not exactly the same, the predicate f captures only the positive aspect of the function, but the problem type is the same. Take the following Prolog program:
f(_, 1, s(1)).
f(1, s(X), s(s(Y))) :- f(1, X, Y).
f(s(X), s(Y), T) :- f(s(X), Y, Z), f(X, Z, T).
d(1).
d(s(X)) :- d(X).
Whats the theoretical logical outcome of the last query, and can you demonstrably have a computer program in our time and space that produces the outcome, i.e. post the program on gist and everybody can run it?
?- f(X,X,Y).
X = 1,
Y = s(1)
X = s(1),
Y = s(s(s(1)))
X = s(s(1)),
Y = s(s(s(s(s(s(s(s(s(s(...))))))))))
ERROR: Out of global stack
?- f(s(s(s(s(1)))), s(s(s(s(1)))), X), d(X).
If the program that does the job of certifying the result is not a Prolog interpreter itself like here, what would do the job especially suited for this Prologish problem formulation?
One solution: Abstract interpretation
Preliminaries
In this answer, I use an interpreter to show that this holds. However, it is not a Prolog interpreter, because it does not interpret the program in exactly the same way Prolog interprets the program.
Instead, it interprets the program in a more abstract way. Such interpreters are therefore called abstract interpreters.
Program representation
Critically, I work directly with the source program, using only modifications that we, by purely algebraic reasoning, know can be safely applied. It helps tremendously for such reasoning that your source program is completely pure by construction, since it only uses pure predicates.
To simplify reasoning about the program, I now make all unifications explicit. It is easy to see that this does not change the meaning of the program, and can be easily automated. I obtain:
f(_, X, Y) :-
X = 1,
Y = s(1).
f(Arg, X, Y) :-
Arg = 1,
X = s(X0),
Y = s(s(Y0)),
f(Arg, X0, Y0).
f(X, Y, T) :-
X = s(X0),
Y = s(Y0),
f(X, Y0, Z),
f(X0, Z, T).
I leave it as an easy exercise to show that this is declaratively equivalent to the original program.
The abstraction
The abstraction I use is the following: Instead of reasoning over the concrete terms 1, s(1), s(s(1)) etc., I use the atom d for each term T for which I can prove that d(T) holds.
Let me show you what I mean by the following interpretation of unification:
interpret(d = N) :- d(N).
This says:
If d(N) holds, then N is to be regarded identical to the atom d, which, as we said, shall denote any term for which d/1 holds.
Note that this differs significantly from what an actual unification between concrete terms d and N means! For example, we obtain:
?- interpret(X = s(s(1))).
X = d.
Pretty strange, but I hope you can get used to it.
Extending the abstraction
Of course, interpreting a single unification is not enough to reason about this program, since it also contains additional language elements.
I therefore extend the abstract interpretation to:
conjunction
calls of f/3.
Interpreting conjunctions is easy, but what about f/3?
Incremental derivations
If, during abstract interpretation, we encounter the goal f(X, Y, Z), then we know the following: In principle, the arguments can of course be unified with any terms for which the goal succeeds. So we keep track of those arguments for which we know the query can succeed in principle.
We thus equip the predicate with an additional argument: A list of f/3 goals that are logical consequences of the program.
In addition, we implement the following very important provision: If we encounter a unification that cannot be safely interpreted in abstract terms, then we throw an error instead of failing silently. This may for example happen if the unification would fail when regarded as an abstract interpretation although it would succeed as a concrete unification, or if we cannot fully determine whether the arguments are of the intended domain. The primary purpose of this provision is to avoid unintentional elimination of actual solutions due to oversights in the abstract interpreter. This is the most critical aspect in the interpreter, and any proof-theoretic mechanism will face closely related questions (how can we ensure that no proofs are missed?).
Here it is:
interpret(Var = N, _) :-
must_be(var, Var),
must_be(ground, N),
d(N),
Var = d.
interpret((A,B), Ds) :-
interpret(A, Ds),
interpret(B, Ds).
interpret(f(A, B, C), Ds) :-
member(f(A, B, C), Ds).
Quis custodiet ipsos custodes?
How can we tell whether this is actually correct? That's the tough part! In fact, it turns out that the above is not sufficient to be certain to catch all cases, because it may simply fail if d(N) does not hold. It is obviously not acceptable for the abstract interpreter to fail silently for cases it cannot handle. So we need at least one more clause:
interpret(Var = N, _) :-
must_be(var, Var),
must_be(ground, N),
\+ d(N),
domain_error(d, N).
In fact, an abstract interpreter becomes a lot less error-prone when we reason about ground terms, and so I will use the atom any to represent "any term at all" in derived answers.
Over this domain, the interpretation of unification becomes:
interpret(Var = N, _) :-
must_be(ground, N),
( var(Var) ->
( d(N) -> Var = d
; N = s(d) -> Var = d
; N = s(s(d)) -> Var = d
; domain_error(d, N)
)
; Var == any -> true
; domain_error(any, Var)
).
In addition, I have implemented further cases of the unification over this abstract domain. I leave it as an exercise to ponder whether this correctly models the intended semantics, and to implement further cases.
As it will turn out, this definition suffices to answer the posted question. However, it clearly leaves a lot to be desired: It is more complex than we would like, and it becomes increasingly harder to tell whether we have covered all cases. Note though that any proof-theoretic approach will face closely corresponding issues: The more complex and powerful it becomes, the harder it is to tell whether it is still correct.
All derivations: See you at the fixpoint!
It now remains to deduce everything that follows from the original program.
Here it is, a simple fixpoint computation:
derivables(Ds) :-
functor(Head, f, 3),
findall(Head-Body, clause(Head, Body), Clauses),
derivables_fixpoint(Clauses, [], Ds).
derivables_fixpoint(Clauses, Ds0, Ds) :-
findall(D, clauses_derivable(Clauses, Ds0, D), Ds1, Ds0),
term_variables(Ds1, Vs),
maplist(=(any), Vs),
sort(Ds1, Ds2),
( same_length(Ds2, Ds0) -> Ds = Ds0
; derivables_fixpoint(Clauses, Ds2, Ds)
).
clauses_derivable(Clauses, Ds0, Head) :-
member(Head-Body, Clauses),
interpret(Body, Ds0).
Since we are deriving ground terms, sort/2 removes duplicates.
Example query:
?- derivables(Ds).
ERROR: Arguments are not sufficiently instantiated
Somewhat anticlimactically, the abstract interpreter is unable to process this program!
Commutativity to the rescue
In a proof-theoretic approach, we search for, well, proofs. In an interpreter-based approach, we can either improve the interpreter or apply algebraic laws to transform the source program in a way that preserves essential properties.
In this case, I will do the latter, and leave the former as an exercise. Instead of searching for proofs, we are searching for equivalent ways to write the program so that our interpreter can derive the desired properties. For example, I now use commutativity of conjunction to obtain:
f(_, X, Y) :-
X = 1,
Y = s(1).
f(Arg, X, Y) :-
Arg = 1,
f(Arg, X0, Y0),
X = s(X0),
Y = s(s(Y0)).
f(X, Y, T) :-
f(X, Y0, Z),
f(X0, Z, T),
X = s(X0),
Y = s(Y0).
Again, I leave it as an exercise to carefully check that this program is declaratively equivalent to your original program.
iamque opus exegi, because:
?- derivables(Ds).
Ds = [f(any, d, d)].
This shows that in each solution of f/3, the last two arguments are always terms for which d/1 holds! In particular, it also holds for the sample arguments you posted, even if there is no hope to ever actually compute the concrete terms!
Conclusion
By abstract interpretation, we have shown:
for all X where f(_, _, X) holds, d(X) also holds
beyond that, for all Y where f(_, Y, _) holds, d(Y) also holds.
The question only asked for a special case of the first property. We have shown significantly more!
In summary:
If f(_, Y, X) holds, then d(X) holds and d(Y) holds.
Prolog makes it comparatively easy and convenient to reason about Prolog programs. This often allows us to derive interesting properties of Prolog programs, such as termination properties and type information.
Please see Reasoning about programs for references and more explanation.
+1 for a great question and reference.

Steadfastness: Definition and its relation to logical purity and termination

So far, I have always taken steadfastness in Prolog programs to mean:
If, for a query Q, there is a subterm S, such that there is a term T that makes ?- S=T, Q. succeed although ?- Q, S=T. fails, then one of the predicates invoked by Q is not steadfast.
Intuitively, I thus took steadfastness to mean that we cannot use instantiations to "trick" a predicate into giving solutions that are otherwise not only never given, but rejected. Note the difference for nonterminating programs!
In particular, at least to me, logical-purity always implied steadfastness.
Example. To better understand the notion of steadfastness, consider an almost classical counterexample of this property that is frequently cited when introducing advanced students to operational aspects of Prolog, using a wrong definition of a relation between two integers and their maximum:
integer_integer_maximum(X, Y, Y) :-
Y >= X,
!.
integer_integer_maximum(X, _, X).
A glaring mistake in this—shall we say "wavering"—definition is, of course, that the following query incorrectly succeeds:
?- M = 0, integer_integer_maximum(0, 1, M).
M = 0. % wrong!
whereas exchanging the goals yields the correct answer:
?- integer_integer_maximum(0, 1, M), M = 0.
false.
A good solution of this problem is to rely on pure methods to describe the relation, using for example:
integer_integer_maximum(X, Y, M) :-
M #= max(X, Y).
This works correctly in both cases, and can even be used in more situations:
?- integer_integer_maximum(0, 1, M), M = 0.
false.
?- M = 0, integer_integer_maximum(0, 1, M).
false.
| ?- X in 0..2, Y in 3..4, integer_integer_maximum(X, Y, M).
X in 0..2,
Y in 3..4,
M in 3..4 ? ;
no
Now the paper Coding Guidelines for Prolog by Covington et al., co-authored by the very inventor of the notion, Richard O'Keefe, contains the following section:
5.1 Predicates must be steadfast.
Any decent predicate must be “steadfast,” i.e., must work correctly if its output variable already happens to be instantiated to the output value (O’Keefe 1990).
That is,
?- foo(X), X = x.
and
?- foo(x).
must succeed under exactly the same conditions and have the same side effects.
Failure to do so is only tolerable for auxiliary predicates whose call patterns are
strongly constrained by the main predicates.
Thus, the definition given in the cited paper is considerably stricter than what I stated above.
For example, consider the pure Prolog program:
nat(s(X)) :- nat(X).
nat(0).
Now we are in the following situation:
?- nat(0).
true.
?- nat(X), X = 0.
nontermination
This clearly violates the property of succeeding under exactly the same conditions, because one of the queries no longer succeeds at all.
Hence my question: Should we call the above program not steadfast? Please justify your answer with an explanation of the intention behind steadfastness and its definition in the available literature, its relation to logical-purity as well as relevant termination notions.
In 'The craft of prolog' page 96 Richard O'Keef says 'we call the property of refusing to give wrong answers even when the query has an unexpected form (typically supplying values for what we normally think of as inputs*) steadfastness'
*I am not sure if this should be outputs. i.e. in your query ?- M = 0, integer_integer_maximum(0, 1, M). M = 0. % wrong! M is used as an input but the clause has been designed for it to be an output.
In nat(X), X = 0. we are using X as an output variable not an input variable, but it has not given a wrong answer, as it does not give any answer. So I think under that definition it could be steadfast.
A rule of thumb he gives is 'postpone output unification until after the cut.' Here we have not got a cut, but we still want to postpone the unification.
However I would of thought it would be sensible to have the base case first rather than the recursive case, so that nat(X), X = 0. would initially succeed .. but you would still have other problems..

How do I freeze a goal for a list of variables?

My ultimate goal is to make a reified version of automaton/3, that freezes if there are any variables in the sequence passed to it. i.e. I dont want the automaton to instantiate variables.
(fd_length/3, if_/3 etc as defined by other people here on so).
To start with I have a reified test for single variables:
var_t(X,T):-
var(X) ->
T=true;
T=false.
This allows me to implement:
if_var_freeze(X,Goal):-
if_(var_t(X),freeze(X,Goal),Goal).
So I can do something like:
?-X=bob,Goal =format("hello ~w\n",[X]),if_var_freeze(X,Goal).
Which will behave the same as:
?-Goal =format("hello ~w\n",[X]),if_var_freeze(X,Goal),X=bob.
How do I expand this to work on a list of variables so that Goal is only called once, when all the vars have been instantiated?
In this method if I have more than one variable I can get this behaviour which I don't want:
?-List=[X,Y],Goal = format("hello, ~w and ~w\n",List),
if_var_freeze(X,Goal),
if_var_freeze(Y,Goal),X=bob.
hello, bob and _G3322
List = [bob, Y],
X = bob,
Goal = format("hello, ~w and ~w\n", [bob, Y]),
freeze(Y, format("hello, ~w and ~w\n", [bob, Y])).
I have tried:
freeze_list(List,Goal):-
freeze_list_h(List,Goal,FrozenList),
call(FrozenList).
freeze_list_h([X],Goal,freeze(X,Goal)).
freeze_list_h(List,Goal,freeze(H,Frozen)):-
List=[H|T],
freeze_list_h(T,Goal,Frozen).
Which works like:
?- X=bob,freeze_list([X,Y,Z],format("Hello ~w, ~w and ~w\n",[X,Y,Z])),Y=fred.
X = bob,
Y = fred,
freeze(Z, format("Hello ~w, ~w and ~w\n", [bob, fred, Z])) .
?- X=bob,freeze_list([X,Y,Z],format("Hello ~w, ~w and ~w\n",[X,Y,Z])),Y=fred,Z=sue.
Hello bob, fred and sue
X = bob,
Y = fred,
Z = sue .
Which seems okay, but I am having trouble applying it to automaton/3.
To reiterate the aim is to make a reified version of automaton/3, that freezes if there are any variables in the sequence passed to it. i.e. I don't want the automaton to instantiate variables.
This is what I have:
ga(Seq,G) :-
G=automaton(Seq, [source(a),sink(c)],
[arc(a,0,a), arc(a,1,b),
arc(b,0,a), arc(b,1,c),
arc(c,0,c), arc(c,1,c)]).
max_seq_automaton_t(Max,Seq,A,T):-
Max #>=L,
fd_length(Seq,L),
maplist(var_t,Seq,Var_T_List), %find var_t for each member of seq
maplist(=(false),Var_T_List), %check that all are false i.e no uninstaninated vars
call(A),!,
T=true.
max_seq_automaton_t(Max,Seq,A,T):-
Max #>=L,
fd_length(Seq,L),
maplist(var_t,Seq,Var_T_List), %find var_t for each member of seq
maplist(=(false),Var_T_List), %check that all are false i.e no uninstaninated vars
\+call(A),!,
T=false.
max_seq_automaton_t(Max,Seq,A,true):-
Max #>=L,
fd_length(Seq,L),
maplist(var_t,Seq,Var_T_List), %find var_t for each
memberd_t(true,Var_T_List,true), %at least one var
freeze_list_h(Seq,A,FrozenList),
call(FrozenList),
call(A).
max_seq_automaton_t(Max,Seq,A,false):-
Max #>=L,
fd_length(Seq,L),
maplist(var_t,Seq,Var_T_List), %find var_t for each
memberd_t(true,Var_T_List,true), %at least one var
freeze_list_h(Seq,A,FrozenList),
call(FrozenList),
\+call(A).
Which does not work, The following goal should be frozen until X is instantiated:
?- Seq=[X,1],ga(Seq,A),max_seq_automaton_t(3,Seq,A,T).
Seq = [1, 1],
X = 1,
A = automaton([1, 1], [source(a), sink(c)], [arc(a, 0, a), arc(a, 1, b), arc(b, 0, a), arc(b, 1, c), arc(c, 0, c), arc(c, 1, c)]),
T = true
Update This is what I now have which I think works as I originally intended but I am digesting what #Mat has said to think if this is actually what I want. Will update further tomorrow.
goals_to_conj([G|Gs],Conj) :-
goals_to_conj_(Gs,G,Conj).
goals_to_conj_([],G,nonvar(G)).
goals_to_conj_([G|Gs],G0,(nonvar(G0),Conj)) :-
goals_to_conj_(Gs,G,Conj).
max_seq_automaton_t(Max,Seq,A,T):-
Max #>=L,
fd_length(Seq,L),
maplist(var_t,Seq,Var_T_List), %find var_t for each member of seq
maplist(=(false),Var_T_List), %check that all are false i.e no uninstaninated vars
call(A),!,
T=true.
max_seq_automaton_t(Max,Seq,A,T):-
Max #>=L,
fd_length(Seq,L),
maplist(var_t,Seq,Var_T_List), %find var_t for each member of seq
maplist(=(false),Var_T_List), %check that all are false i.e no uninstaninated vars
\+call(A),!,
T=false.
max_seq_automaton_t(Max,Seq,A,T):-
Max #>=L,
fd_length(Seq,L),
maplist(var_t,Seq,Var_T_List), %find var_t for each
memberd_t(true,Var_T_List,true), %at least one var
goals_to_conj(Seq,GoalForWhen),
when(GoalForWhen,(A,T=true)).
max_seq_automaton_t(Max,Seq,A,T):-
Max #>=L,
fd_length(Seq,L),
maplist(var_t,Seq,Var_T_List), %find var_t for each
memberd_t(true,Var_T_List,true), %at least one var
goals_to_conj(Seq,GoalForWhen),
when(GoalForWhen,(\+A,T=false)).
In my view, you are making great progress with Prolog. At this point it makes sense to proceed a bit more prudently though. All the things you are asking for can, in principle, be solved easily. You only need a generalization of freeze/2, which is available as when/2.
However, let us take a step back and more deeply consider what is actually going on here.
Declaratively, when we state a constraint, we mean that it holds. We do not mean "It holds only when everything is instantiated", because that would reduce the constraint to a mere checker, leading to a "generate-and-test" approach. The point of constraints is exactly to prune whenever possible, leading to a much reduced search space in many cases.
Exactly the same holds for reified constraints. When we post a reified constraint, we state that the reification holds. Not only in cases where everything is instantiated, but always. The point is exactly that the (reified) constraint can be used in all directions. If the constraint that is being reified is already entailed, we get to know it. Likewise, if it cannot hold, we get to know it. If either possibility may be the case, we need to search explicitly for solutions, or determine that none exist. If we want to insist that the constraint that is being reified holds, it is easily possible; etc.
However, the point in all cases is exactly that we can focus on the declarative semantics of the constraint, very free from extra-logical, procedural considerations like what is being instantiated and when. If I answered your literal question, it would move you closer to operational considerations, much closer than you probably need or want in actuality.
Therefore, I am not going to answer your literal question. But I will give you a solution to your actual, underlying issue.
The point is to reifiy automaton/3. A constraint reification will not by itself prune anything as long as it is open whether the constraint that is being reified actually holds or not. Only when we insist that the constraint that is being reified holds does propagation occur.
It is easy to reify automaton/3, by reifying the conjunction of constraints that constitute its decomposition. Here is one way to do it, based on code that is freely available in SWI-Prolog:
:- use_module(library(clpfd)).
automaton(Vs, Ns, As, T) :-
must_be(list(list), [Vs,Ns,As]),
include_args1(source, Ns, Sources),
include_args1(sink, Ns, Sinks),
phrase((arcs_relation(As, Relation),
nodes_nums(Sinks, SinkNums0),
nodes_nums(Sources, SourceNums0)), [[]-0], _),
phrase(transitions(Vs, Start, End), Tuples),
list_to_drep(SinkNums0, SinkDrep),
list_to_drep(SourceNums0, SourceDrep),
( Start in SourceDrep #/\
End in SinkDrep #/\
tuples_in(Tuples, Relation)) #<==> T.
include_args1(Goal, Ls0, As) :-
include(Goal, Ls0, Ls),
maplist(arg(1), Ls, As).
list_to_drep([L|Ls], Drep) :-
foldl(drep_, Ls, L, Drep).
drep_(L, D0, D0\/L).
transitions([], S, S) --> [].
transitions([Sig|Sigs], S0, S) --> [[S0,Sig,S1]],
transitions(Sigs, S1, S).
nodes_nums([], []) --> [].
nodes_nums([Node|Nodes], [Num|Nums]) -->
node_num(Node, Num),
nodes_nums(Nodes, Nums).
arcs_relation([], []) --> [].
arcs_relation([arc(S0,L,S1)|As], [[From,L,To]|Rs]) -->
node_num(S0, From),
node_num(S1, To),
arcs_relation(As, Rs).
node_num(Node, Num), [Nodes-C] --> [Nodes0-C0],
{ ( member(N-I, Nodes0), N == Node ->
Num = I, C = C0, Nodes = Nodes0
; Num = C0, C is C0 + 1, Nodes = [Node-C0|Nodes0]
) }.
sink(sink(_)).
source(source(_)).
Note that this propagates nothing whatsoever as long as T is unknown.
I now use the following definition for a few sample queries:
seq(Seq, T) :-
automaton(Seq, [source(a),sink(c)],
[arc(a,0,a), arc(a,1,b),
arc(b,0,a), arc(b,1,c),
arc(c,0,c), arc(c,1,c)], T).
Examples:
?- seq([X,1], T).
Result (omitted): Constraints are posted, nothing is propagated.
Next example:
?- seq([X,1], T), X = 3.
X = 3,
T = 0.
Clearly, the reified automaton/3 constraint does not hold in this case. However, the reifying constraint of course still holds, as always, and this is the reason why T=0 in this case.
Next example:
?- seq([1,1], T), indomain(T).
T = 0 ;
T = 1.
Oh-oh! What is going on here? How can it be that the constraint is both true and false? This is because we do not see all constraints that are actually posted in this example. Use call_residue_vars/2 to see the whole truth.
In fact, try it on the simpler example:
?- call_residue_vars(seq([1,1],0), Vs).
The pending residual constraints that still need to be satisfied in this case are:
_G1496 in 0..1,
_G1502#/\_G1496#<==>_G1511,
tuples_in([[_G1505,1,_G1514]], [[0,0,0],[0,1,1],[1,0,0],[1,1,2],[2,0,2], [2,1,2]])#<==>_G825,
tuples_in([[_G831,1,_G827]], [[0,0,0],[0,1,1],[1,0,0],[1,1,2],[2,0,2],[2,1,2]])#<==>_G826,
_G829 in 0#<==>_G830,
_G830 in 0..1,
_G830#/\_G828#<==>_G831,
_G828 in 0..1,
_G827 in 2#<==>_G828,
_G829 in 0..1,
_G829#/\_G826#<==>0,
_G826 in 0..1,
_G825 in 0..1
So, the above only holds if these constraints, which are said to still flounder, also hold.
Here is an auxiliary definition that helps you label remaining finite domain variables. It suffices for this example:
finite(V) :-
fd_dom(V, L..U),
dif(L, inf),
dif(U, sup).
We can now paste back the residual program (which consists of CLP(FD) constraints), and use label_fixpoint/1 to label variables whose domain is finite:
?- Vs0 = [_G1496, _G1499, _G1502, _G1505, _G1508, _G1511, _G1514, _G1517, _G1520, _G1523, _G1526],
_G1496 in 0..1,
_G1502#/\_G1496#<==>_G1511,
tuples_in([[_G1505,1,_G1514]], [[0,0,0],[0,1,1],[1,0,0],[1,1,2],[2,0,2], [2,1,2]])#<==>_G825,
tuples_in([[_G831,1,_G827]], [[0,0,0],[0,1,1],[1,0,0],[1,1,2],[2,0,2],[2,1,2]])#<==>_G826,
_G829 in 0#<==>_G830, _G830 in 0..1,
_G830#/\_G828#<==>_G831, _G828 in 0..1,
_G827 in 2#<==>_G828, _G829 in 0..1,
_G829#/\_G826#<==>0, _G826 in 0..1, _G825 in 0..1,
include(finite, Vs0, Vs),
label(Vs).
Note that we cannot directly use labeling in the original program, i.e., we cannot do:
?- call_residue_vars(seq([1,1],0), Vs), <label subset of Vs>.
because call_residue_vars/2 also brings internal variables to the surface that, although they have a domain assigned and look like regular CLP(FD) variables, are not meant to directly participate in any labeling.
In contrast, the residual program can be used without any problem for further reasoning, and it is in fact meant to be used that way.
In this concrete case, after labeling the variables whose domains are still finite in the case above, some constraints still remain. They are of the form:
tuples_in([[_G1487,1,_G1496]], [[0,0,0],[0,1,1],[1,0,0],[1,1,2],[2,0,2],[2,1,2]])#<==>_G1518
Exercise: Does it follow from this, however indirectly, that the original query, i.e., seq([1,1],0), cannot hold?
So, to summarize:
Constraint reification does not in itself cause propagation of the constraint that is being reified.
Constraint reification often lets you detect that a constraint cannot hold.
In general, CLP(FD) propagation is necessarily incomplete, i.e., we cannot be sure that there is a solution just because our query succeeds.
labeling/2 lets you see whether there are concrete solutions, if domains are finite.
To see all pending constraints, wrap your query in call_residue_vars/2.
As long as pending constraints remain, it is only a conditional answer.
Recommendation: To make sure that no floundering constraints remain, wrap your query in call_residue_vars/2 and look for any residual constraints on the toplevel.
Consider using the widely available prolog-coroutining predicate when/2 (for details, consider reading the SICStus Prolog manual page on when/2).
Note that you can, in principle, implement freeze/2 like this:
freeze(V,Goal) :-
when(nonvar(V),Goal).
What you are implementing appears to me a variation of the following:
delayed_until_ground_t(Goal,T) :-
( ground(Goal)
-> ( call(Goal)
-> T = true
; T = false
)
; T = true, when(ground(Goal),once(Goal))
; T = false, when(ground(Goal), \+(Goal))
).
Delaying goals can be a really nice feature, but be aware of the perils of delaying forever.
Make sure to read and digest the above answer by #mat regarding call_residue_vars/2!

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.

Resources