Swi-Prolog - Finding X Based on Definition - prolog

I am using Swi-Prolog for what I think is a slightly weird use of Prolog. Reason I say that is 'cause I don't know what people use Prolog for normally aside from Watson.
In any case, I am making a prolog program for defining emotions based off what I tell it like:
emotion(anxiety,emotion):-
emotion(anxiety,prime).
emotion(fear,emotion):-
emotion(anxiety,prime),
emotion(when,prime),
emotion(bad,prime).
emotion(horrified,emotion):-
emotion(surprise,prime),
(emotion(fear,emotion);emotion(aversion,prime)).
The primes are unary so they're not the issue.
I can find emotion(X,Y). which will be everything that I defined with two arguments.
The issue is how can I find words based off the definitions? Could I tell prolog to find all emotions that contained some kind of definition of anxiety? Which would technically be anxiety as an emotion, fear and one of the "horrified" since I made it be definable through either surprise and fear (which entails anxiety) or surprise and aversion.
Is there a command I can use or would I have to program something in order to have prolog produce such a list?

I can find emotion(X,Y).
If you actually enter ?- emotion(X,Y). you'll get just false. as answer.
When you will add some of the facts required by these rules, for instance, assert(emotion(anxiety,prime)). you will get X=anxiety Y=emotion.
(I think that you should have distinct predicates for 'raw data' and categorization.)
Prolog allows inspecting programs, the primary 'reflexive' built in is clause/2. On your program:
?- clause(emotion(X,Y),Body).
X = anxiety,
Y = emotion,
Body = emotion(anxiety, prime) ;
X = fear,
Y = emotion,
Body = (emotion(anxiety, prime), emotion(when, prime), emotion(bad, prime)) ;
X = horrified,
Y = emotion,
Body = (emotion(surprise, prime), (emotion(fear, emotion);emotion(aversion, prime))).
This allows to meta interpret programs (see here for a clear introduction), and to inspect any detail, after providing the 'navigation' tools. Of course, a statement like some kind of definition of anxiety must be detailed: does anxiety occurs as primal, etc etc.
For instance
?- [user].
|: occurs(E,emotion(E,_)).
|: occurs(E,(A,B)) :- occurs(E,A);occurs(E,B).
|: occurs(E,(A;B)) :- occurs(E,A);occurs(E,B).
|: % user://1 compiled 0,20 sec, 4 clauses
true.
?- findall(E, (clause(emotion(E,_),B), occurs(anxiety,B)),L).
L = [anxiety, fear].

Related

Setting types of unbound variables in Prolog

I'm trying to find a way to set the type of a variable before it has been bound to a value. Unfortunately, the integer/1 predicate cannot be used for this purpose:
%This goal fails if Int is an unbound variable.
get_first_int(Int,List) :-
integer(Int),member(Int,List),writeln(Int).
I wrote a predicate called is_int that attempts to check the type in advance, but it does not work as I expected. It allows the variable to be bound to an atom instead of an integer:
:- initialization(main).
%This prints 'a' instead of 1.
main :- get_first_int(Int,[a,b,c,1]),writeln(Int).
get_first_int(Int,List) :-
is_integer(Int),member(Int,List).
is_integer(A) :- integer(A);var(A).
Is it still possible to set the type of a variable that is not yet bound to a value?
In SWI-Prolog I have used when/2 for similar situations. I really don't know if it is a good idea, it definitely feels like a hack, but I guess it is good enough if you just want to say "this variable can only become X" where X is integer, or number, or atom and so on.
So:
will_be_integer(X) :- when(nonvar(X), integer(X)).
and then:
?- will_be_integer(X), member(X, [a,b,c,1]).
X = 1.
But I have the feeling that almost always you can figure out a less hacky way to achieve the same. For example, why not just write:
?- member(X, [a,b,c,1]), integer(X).
???
Specific constraints for integers
In addition to what Boris said, I have a recommendation for the particular case of integers: Consider using CLP(FD) constraints to express that a variable must be of type integer. To express only this quite general requirement, you can post a CLP(FD) constraint that necessarily holds for all integers.
For example:
?- X in inf..sup.
X in inf..sup.
From this point onwards, X can only be instantiated to an integer. Everything else will yield a type error.
For example:
?- X in inf..sup, X = 3.
X = 3.
?- X in inf..sup, X = a.
ERROR: Type error: `integer' expected, found `a' (an atom)
Declaratively, you can always replace a type error with silent failure, since no possible additional instantiation can make the program succeed if this error arises.
Thus, in case you prefer silent failure over this type error, you can obtain it with catch/3:
?- X in inf..sup, catch(X = a, error(type_error(integer,_),_), false).
false.
CLP(FD) constraints are tailor-made for integers, and let you express also further requirements for this specific domain in a convenient way.
Case-specific advice
Let us consider your specific example of get_first_int/2. First, let us rename it to list_first_integer/3 so that it is clear what each argument is, and also to indicate that we fully intend to use it in several directions, not just to "get", but also to test and ideally to generate lists and integers that are in this relation.
Second, note that this predicate is rather messy, since it impurely depends on the instantiation of the list and integer, a property which cannot be expressed in first-order logic but rather depends on something outside of this logic. If we accept this, then one quite straight-forward way to do what you primarily want is to write it as:
list_first_integer(Ls, I) :-
once((member(I0, Ls), integer(I0))),
I = I0.
This works as long as the list is sufficiently instantiated, which implicitly seems to be the case in your examples, but definitely need not be the case in general. For example, with fully instantiated lists, we get:
?- list_first_integer([a,b,c], I).
false.
?- list_first_integer([a,b,c,4], I).
I = 4.
?- list_first_integer([a,b,c,4], 3).
false.
In contrast, if the list is not sufficiently instantiated, then we have the following major problems:
?- list_first_integer(Ls, I).
nontermination
and further:
?- list_first_integer([X,Y,Z], I).
false.
even though a more specific instantiation succeeds:
?- X = 0, list_first_integer([X,Y,Z], I).
X = I, I = 0.
Core problem: Defaulty representation
The core problem is that you are reasoning here about defaulty terms: A list element that is still a variable may either be instantiated to an integer or to any other term in the future. A clean way out is to design your data representation to symbolically distinguish the possible cases. For example, let us use the wrapper i/1 to denote an integer, and o/1 to denote any other kind of term. With this representation, we can write:
list_first_integer([i(I)|_], I).
list_first_integer([o(_)|Ls], I) :-
list_first_integer(Ls, I).
Now, we get correct results:
?- list_first_integer([X,Y,Z], I).
X = i(I) ;
X = o(_12702),
Y = i(I) ;
X = o(_12702),
Y = o(_12706),
Z = i(I) ;
false.
?- X = i(0), list_first_integer([X,Y,Z], I).
X = i(0),
I = 0 ;
false.
And the other examples also still work, if we only use the clean data representation:
?- list_first_integer([o(a),o(b),o(c)], I).
false.
?- list_first_integer([o(a),o(b),o(c),i(4)], I).
I = 4 ;
false.
?- list_first_integer([o(a),o(b),o(c),i(4)], 3).
false.
The most general query now allows us to generate solutions:
?- list_first_integer(Ls, I).
Ls = [i(I)|_16880] ;
Ls = [o(_16884), i(I)|_16890] ;
Ls = [o(_16884), o(_16894), i(I)|_16900] ;
Ls = [o(_16884), o(_16894), o(_16904), i(I)|_16910] ;
etc.
The price you have to pay for this generality lies in these symbolic wrappers. As you seem to care about correctness and also about generality of your code, I consider this a bargain in comparison to more error prone defaulty approaches.
Synthesis
Note that CLP(FD) constraints can be naturally used together with a clean representation. For example, to benefit from more finely grained type errors as explained above, you can write:
list_first_integer([i(I)|_], I) :- I in inf..sup.
list_first_integer([o(_)|Ls], I) :-
list_first_integer(Ls, I).
Now, you get:
?- list_first_integer([i(a)], I).
ERROR: Type error: `integer' expected, found `a' (an atom)
Initially, you may be faced with a defaulty representation. In my experience, a good approach is to convert it to a clean representation as soon as you can, for the sake of the remainder of your program in which you can then distinguish all cases symbolically in such a way that no ambiguity remains.

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..

Tree leaf traversal in Prolog

I experience some issues when I'm training prolog exercises,the problem below is,
The predicate defines what it means to be a tree, and can be used to test whether a term is a tree:
tree(t(L,R)) :- tree(L), tree(R).
tree(T) :- T\=t(_ , _).
By using this predicate you can find an element in a tree, (called a leaf):
leaf(t(L,R),E) :- leaf(L,E); leaf(R,E).
leaf(T,T) :- T\=t(_ , _).
So here have two problem, first is write predicate elements/2 that produces a list of the elements as they are found in the leafs of a tree in the first argument in a left-to-right order!
The second is write a predicate same content/2 that succeeds exactly when two trees contain the same elements in the same order! Duplicates are significant.
Hope can get anyone good at prolog can help me, thanks a lot.
Both tree/1 and leaf/1 are defaulty1,2!
Why not use a cleaner representation like this?
is_tree(leaf(_)).
is_tree(bin(L,R)) :-
is_tree(L),
is_tree(R).
Note that:
is_tree/1 is more versatile than tree/1 and leaf/1: it can generate as well as test trees—and even do a little of both (if the argument is partially instantiated).
is_tree/1 never gives logically unsound answers—no matter which "mode" it is used in.
Some sample uses of is_tree/1:
?- is_tree(T). % generate
T = leaf(_A)
; T = bin(leaf(_A),leaf(_B))
; T = bin(leaf(_A),bin(leaf(_B),leaf(_C)))
; T = bin(leaf(_A),bin(leaf(_B),bin(leaf(_C),leaf(_D))))
...
?- is_tree(bin(leaf(1),bin(leaf(2),3))). % test
false.
?- is_tree(bin(leaf(1),bin(leaf(2),leaf(3)))). % test
true.
?- T = bin(bin(leaf(1),2),_), is_tree(T). % do both (or at least try)
false.
?- T = bin(bin(leaf(1),leaf(2)),_), is_tree(T). % do both
T = bin(bin(leaf(1),leaf(2)),leaf(_A))
T = bin(bin(leaf(1),leaf(2)),bin(leaf(_A),leaf(_B)))
T = bin(bin(leaf(1),leaf(2)),bin(leaf(_A),bin(leaf(_B),leaf(_C))))
...
Coming back to your question on how to implement elements/2 and content/2... Use dcg!
leaves(leaf(E)) --> [E].
leaves(bin(L,R)) --> leaves(L), leaves(R).
same_content(A,B) :-
phrase(leaves(A),Ls),
phrase(leaves(B),Ls).
Sample query:
?- same_content(bin(leaf(1),bin(leaf(2),leaf(3))),
bin(bin(leaf(1),leaf(2)),leaf(3))).
true.
Footnote 1: This rock-solid treatise on teaching Prolog discusses many common obstacles, including defaultyness.
Footnote 2: In this answer #mat explains on how defaultyness in Prolog impedes declarative debugging and reasoning.

About c() predicate in prolog

I have the code
newplan(State, [c(StateList)], [], State):- satisfied( State, StateList).
and I don't know what c() predicate does. I tried to search internet for answers but I couldn't find. Please help me.
In this code c/1 is just a structure. Prolog is a little different from most languages, in that a structure and a predicate (what might be thought of as a function call in another language) share syntax. So here c/1 doesn't do anything, it's just a marker that (presumably) is granted meaning through something else in the code which you haven't shared with us.
Let me give you a concrete example.
eval(c(X), X2) :- X2 is (X*2) + 3.
eval(q(X), X2) :- X2 is X / 3.
something_to_do(c(14)).
something_to_do(q(21)).
In this code, c/1 and q/1 do not do anything. If you query something_to_do/1 you'll get structures back:
?- something_to_do(X).
X = c(14) ;
X = q(21) ;
false.
But if you then pass that structure to eval/2 it does something depending on which structure it gets. So you could say eval/2 imbues the structure q/1 and c/1 with meaning (though "imbuing meaning" is not in any sense official Prolog nomenclature).
?- something_to_do(X), eval(X, Y).
X = c(14), Y = 31 ;
X = q(21), Y = 7 ;
false.
It's the same story here. You're going to have to search your codebase and find out what c/1 means in it, because it is not a built-in predicate.
Note: it's possible to have structures and predicates with the same name in the same codebase at the same time. For instance, I could add a predicate like
q(foo).
q(bar).
q(X) :- even(X).
and this predicate does not in any sense overlap with the q/1 structure above. This is just one of those fun confusing things about Prolog (later on it turns out to be powerful and grand). There is an acute difference between creating structures and attempting to unify goals.

DCG for idiomatic phrase preference

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...).

Resources