Prolog: Passing Implicit Parameter / Predicated Evaluation - prolog

I am looking for a reliable way to pass an implicit parameter among predicates, e.g.,
p(Context, Args) :- goal(Args).
where goal(Args) should be expanded to something like interpret(Context, goal, Args).
However, since I don't know whether a term will be evaluated as a goal or used as data, I'd like to attach Context to goal as extra data without modifying its actual structure.
Is there any way to do this?
Also, I'd need some way to hook into the evaluation of a term, then fetch its context and call interpret.
Any Ideas?
I am using SWI Prolog, a portable solution would be fine, but is not required.
Edit:
In pseudocode, what I am roughly looking for is the following:
term_expansion((Head :- Body), (Head :- Body)) :-
arg(1, Head, Context),
forall T: CompoundTerm in Body =>
set_term_attribute(T, context, Context).
on_evaluate(T) :-
get_term_attribute(T, context, Context) -> interpret(Context, T) ;
call(T).

Check out the important predicates term_expansion/2 and goal_expansion/2.
They allow you to rewrite clauses at compilation time, and these or similar constructs are supported by all serious Prolog systems to provide an expansion mechanism for Prolog code.
Definite clause grammars (see dcg for more information) are often implemented using such mechanisms. In fact, to pass around a context, DCG notation is itself often already sufficient, so you may not even have to rewrite the code yourself in your use case.
See the DCG resources for more information.

Easy. Use a Logtalk parametric object. You can use this solution with twelve Prolog systems, including SWI-Prolog. For example:
:- object(foo(_Parameter1, _Parameter2)).
:- public(p1/1).
p1(Parameter1) :-
parameter(1, Parameter1).
:- public(p2/1).
p2(Parameter2) :-
parameter(2, Parameter2).
:- end_object.
?- foo(1,2)::p1(P1).
P1 = 1.
?- foo(1,2)::p2(P2).
P2 = 2.
The parameters are logical variables, with all the benefits and potential that entails. The parameters are implicitly shared by all object predicate clauses. In SWI-Prolog, you can even use dicts for parameter values.
It's also easy to provide default parameter values. For example:
:- object(foo, extends(foo(a,b))).
:- end_object.
?- foo::p1(P1).
P1 = a.
?- foo::p2(P2).
P2 = b.
You can find several examples of using parametric objects in the Logtalk distribution.

Related

Functional patterns in Prolog

How do I create a predicate that takes another predicate and returns a derived version of it?
For example, pairwise predicates can be fairly mechanically extended to apply to lists:
all_whatever(_, []).
all_whatever(X, [Y|T]) :-
whatever(X, Y),
all_whatever(X, T).
What would be the definition of
pairwise_listwise(whatever, all_whatever).
If it's not possible/common/clunky/violates principles, what would be the alternative pattern?
There are two different ways to achieve what you want. The simplest, and likely preferred, way is to define a meta-predicate that takes any binary predicate and applies it to all elements of the list like so:
listwise(_,_,[]).
listwise(P,Y,[X|Xs]) :-
call(P,Y,X),
listwise(P,Y,Xs).
You can then call this as listwise(whatever, Y1, Xs1) to apply whatever to Y1 and each element of Xs1.
This is made possible thanks to the call/N meta-predicate. Note that this meta-predicate can also take partially constructed goals as first argument, so that an alternative formulation could be:
listwise(_,[]).
listwise(P,[X|Xs]) :-
call(P,X),
listwise(P,Xs).
Which is then called as listwise(whatever(Y1),Xs1). This version of the predicate is actually known as maplist/2 instead of listwise, at least in SWI-Prolog (in module library(apply)) and SICStus Prolog (in module library(lists)).
The second way to achieve what you want (actually closer to what you where asking for) is to actually define a new predicate all_whatever/2 using term expansion. Term expansion is a mechanism to rewrite terms when they are loaded (see e.g. for more details in SWI-Prolog: https://www.swi-prolog.org/pldoc/doc_for?object=term_expansion/2). I am showing here the SWI-Prolog version, which is by defining a clause for the term_expansion/2 predicate. This mechanism works differently in different systems or is altogether missing.
term_expansion(pairwise_listwise(PairPred,ListPred), ExpandedTerm) :-
TerminalCall =.. [ListPred,_,[]],
RecursiveCall =.. [ListPred,Y,[X|Xs]],
SingleCall =.. [PairPred,Y,X],
FinalCall =.. [ListPred,Y,Xs],
ExpandedTerm = [TerminalCall, (RecursiveCall :- (SingleCall, FinalCall))].
In this clause, ExpandedTerm is a list defining the two clauses we want to define and all the terms in it are built from the predicate names using =... One can then define the new predicate as follows:
pairwise_listwise(whatever, all_whatever).
When this code is loaded, that clause will be expanded and replaced by two clauses defining the new predicate all_whatever. And now one can call for instance all_whatever(Y1,Xs1).
My preference goes to the first approach (conceptually simpler and works across Prolog versions) but I think it is also useful to be aware of the existence of the term expansion mechanism as well.

Guidelines for implementing predicates like dif/2

Suppose I have a predicate foo/2 which defines a relation between its first and second argument.
What is the most idiomatic and efficient way to change the implementation of foo/2 such that:
if both of its arguments are ground, it acts as before (succeeds if the relation holds, fails otherwise).
if one of the two arguments (or both) are free, it "constrains" those two arguments so that when they will get grounded, the relation will be checked.
In other words, how to correctly implement the behaviour exhibited by dif/2 but with any kind of user-defined relation?
listing(dif/2). was of little help.
Different Prolog implementations provide different features to accomplish this. The mechanism is variously known as coroutining, delayed goals, constraints, and your Prolog system's manual will provide more information.
Here are two variants, which are available in SICStus Prolog and also some other systems.
block/1 directive
In SICStus Prolog (and possibly some other systems), one way to lift a user-defined predicate to such a constrained version is available via the declarative block declaration.
Interestingly, this does not require any changes to the predicate itself!
Suppose you have an impure version of dif/2, using the non-monotonic (\=)/2 predicate:
madif(X, Y) :-
X \= Y.
Then you can turn it into a delayed version for example with:
:- block madif(-, ?),
madif(?, -).
madif(X, Y) :-
X \= Y.
Sample queries and answers:
| ?- madif(a, b).
yes
| ?- madif(a, X).
user:madif(a,X) ? ;
no
| ?- madif(a, X), X = b.
X = b ? ;
no
| ?- madif(X, Y).
user:madif(X,Y) ? ;
no
As required, the evaluation of the goal is delayed until both arguments are instantiated.
when/2
A second way to accomplish this with SICStus Prolog (and other systems that provide this feature) is to use when/2. This requires changes to the predicate itself.
For example, using when/2, you can implement madif/2 like this:
madif(X, Y) :-
when((ground(X),
ground(Y)), X \= Y).
Sample queries and answers:
| ?- madif(X, a).
prolog:trig_ground(X,[],[X],_A,_A),
prolog:when(_A,(ground(X),ground(a)),user:(X\=a)) ? ;
no
| ?- madif(X, a), X = b.
X = b ? ;
no
First and foremostly,
Take the user's viewpoint
... and not that of an implementer. All too often this is ignored – also in existing constraint implementations. And it shows. So here are the most salient aspects to take into account.
Correctness
Obviously this should hold. It is always better to produce clean errors, mostly instantiation errors, better to flounder forever, even better to loop forever than to fail incorrectly. If all else breaks you can wrap your attempt with freeze(_, G_0). Note that you do need a working toplevel to actually see such floundering goals. SICStus has such a toplevel1, in SWI you need to wrap your query as call_residue_vars(Query_0, Vs) to see all attached constraints.
Consistency
Next you want to ensure that your constraint ensures consistency as much as possible. There are many notions of consistency like, domain and bounds consistency. To take your precise requirement think of difgrn/2 and compare it to the built-in dif/2:
difgrn(X, Y) :-
when((ground(X), ground(Y)), X \== Y).
| ?- difgrn(X, X).
prolog:trig_ground(X,[],[X],_A,_B),
prolog:trig_ground(X,[],[X],_A,_C),
prolog:trig_and(_C,[],_A,_B,_A),
prolog:when(_A,(ground(X),ground(X)),user:(X\==X)) ? ;
no
| ?- dif(X, X).
no
| ?- difgrn([], [_]).
prolog:trig_ground(_A,[],[_A],_B,_C),
prolog:trig_and(_C,[],_B,1,_B),
prolog:when(_B,(ground([]),ground([_A])),user:([]\==[_A]))
| ?- dif([], [_]).
yes
One way to implement dif/2 in full strength is to use the very special condition (?=)/2:
difwh(X,Y) :- when(?=(X,Y), X\==Y).
which should answer your question as best as one can:
In other words, how to correctly implement the behaviour exhibited by dif/2 but with any kind of user-defined relation?
But unfortunately, this does not extend to anything else.
The situation becomes even more complex if one considers consistency between various constraints. Think of X in 1..2, dif(X, 1), dif(X, 2).
Answer projections
(For lack of a better word.) Sometimes you want to see your constraints nicely on the toplevel - and the best way is to represent them as goals that themselves will reestablish the exact state required to represent an answer.
See above trig_ground answers, which certainly could be beautified a bit.
Variable projections
Same as answer projections but possible at any point in time, via frozen/2 or copy_term/3.
Subsumption checking
This is useful for diagnostic purposes and loop checks.
For purely syntactic terms, there is subsumes_term/2 which ignores constraints. A prerequisite to perform an effective test is to connect each involved variable to the actual constraint. Consider the goal freeze(X, Y = a) and imagine some subsumption checking with Y as an argument. If Y is no longer attached to the information (as it usually is with current implementations of freeze/2) you will come to the wrong conclusion that this Y subsumes b.
Note as for the actual example of dif/2, this was the very first constraint ever (1972, Prolog 0). A more elaborate description gives Michel van Caneghem in L'anatomie de Prolog, InterÉditions 1986 and Lee Naish in Papers about MU-Prolog.
1 Half-true. For library(clpfd) you need assert(clpfd:full_answer).

Negation in prolog query is not working

HI i have a simple knowledge database defined as:
carClass('X1','Oil','small').
carClass('X2','gas','big').
carClass('X3','Petrol','big').
carClass('X4','oil','small').
carClass('X5','Oil','small').
carClass('X6','gas','big').
I am trying to write a rule that will answer the query: Display all carClass that runs on 'oil' and IS NOT 'big'.
I am trying to implement it using:
OnOilButNotBig :-
carClass(CarClass,'oil',_),
carClass(CarClass,'oil', \+('big') ),
write(CarClass).
but this is not working.
You have to understand the difference between a predicate and a functor.
If we oversimplify things a bit, a predicate is an identifier at the top level, so carClass/3 is a predicate, write/1 is a predicate and onOilButNotBig/0 is. You can call a predicate. A predicate with filled in arguments is a goal.
A functor on the other hand is an identifier not on the top level. Constants are functors, variables are functors, and functions with arguments are functors. Examples of functors are 'X1', 'oil' and foo(X,bar,qux(2)).
The negation expects a goal. 'big' in this case is not a goal, in fact \+('big') itself is a functor.
You can only solve this by turning the condition into a goal and ensure you will call it. This can be done like:
onOilButNotBig :-
carClass(CarClass,'oil',_),
carClass(CarClass,'oil',X),
\+(X = 'big'),
write(CarClass).
Furthermore I do not really see why you call carClass/3 twice. An equivalent and slightly more efficient program is the following:
onOilButNotBig :-
carClass(CarClass,'oil',X),
\+(X = 'big'),
write(CarClass).
Finally as #Repeat noted, you need to use names that start with a lowercase for predicates and functions.
First things first!
The code doesn't compile1.
Why? Predicate names usually start with lowercase characters2.
My advice: instead of OnOilButNotBig write onOilButNotBig!
To express term inequality, use the right prolog-dif goal(s), like so:
onOilButNotBig :-
dif(X, big),
carClass(CarClass, oil, _),
carClass(CarClass, oil, X),
write(CarClass).
As a side remark, there are a few more issues with your code:
Use side-effect based I/O only when necessary.
In most cases, it is preferable to use the interactive prolog-toplevel for data input/output!
onOilButNotBig(CarClass) :-
dif(X, big),
carClass(CarClass, oil, _),
carClass(CarClass, oil, X).
For the sake of readability, please do not use atoms like 'oil' and 'Oil'.
Pick one and stick to it! I suggest oil (lowercase) which does not need escaping.
The goal carClass(CarClass, oil, _) is completely redundant.
Why? It is a generalisation of the close-by goal carClass(CarClass,oil,X).
Footnote 1: When using b-prolog 8.1, sicstus-prolog 4.3.2, swi-prolog 7.3.14, and xsb 3.6.
Footnote 2: Names can also starting with uppercase characters if the right (escaping with single-quotes) is utilized.
Footnote 3: In general, redundant goals are ok, but they suggest to me your code will likely not behave as intended.

Implementing user-defined arithmetic functions

How can I add a function (e.g., hammingweight) and use it in expressions occuring in the right-hand side is some (is)/2 goal?
Could something like goal_expansion or term_expansion help here?
I acknowledge that this is not a big feature, but it could increase readability of some of my Prolog programs.
Writing a custom (is)/2 predicate (implementing a custom expression evaluator) is do-able, but I would like to keep runtime overhead low, as I don't want to sacrifice readability for runtime overhead in this case.
There is no such provision in ISO Prolog, neither to extend (is)/2 nor to rely on goal expansion. And, looking at the various implementation specific features that are offered by some implementations to this end, there is no generally agreed upon way to do this. So implementing your own (my_is)/2 seems to be the best way to go.
Also note, that this would not only affect (is)/2 but also all other built-ins that use evaluable functors. In particular, all arithmetic comparison built-ins (8.7 Arithmetic comparison) (see this overview) would be affected.
My simple minded (~20 LOC) syntax sugar, lifter, it's based on goal_expansion.
With lifter, the clause
longer(A,B) :-
length(A,º) > length(B,º).
is expanded to
longer(A, B) :-
length(A, C),
length(B, D),
C > D.
You can use Logtalk's term-expansion mechanism, which is portable and works with its twelve supported Prolog compilers (*). Logtalk compiling and loading and loading predicates accept Prolog files and will output the corresponding Prolog expanded files. For example, assuming that the file you want to expand is named source.pl and that your term_expansion/2 and goal_expansion/2 predicate definitions are in a file named expansions.pl, you can do something like:
% first, load the expansion hooks:
| ?- [expansions].
...
% second, expand a file using those hooks:
| ?- logtalk_compile(source, [hook(user)]).
...
You will get the expanded file, which will be (by default) named source_pl.pl (in a directory that will depend on the value of the scratch_directory Logtalk flag). If the expansions are contained in a Prolog module, use above the module name instead of user. If the source.pl file contains a module instead of plain Prolog code, you'll need to define some clauses for the term_expansion/2 predicate to avoid Logtalk compiling the module as an object. But in the simpler case where you're not using modules, the two queries above should suffice.
One feature of Logtalk's term-expansion mechanism that might be useful is that you can mark a term or a goal to not be expanded or further expanded by wrapping it with the {}/1 control construct.
(*) Note that term-expansion mechanism are not standard, not provided by all Prolog implementations, and with significant differences between implementations.
Many Prolog systems don't allow user defined evaluable predicates.
Sometimes the problem is that the evaluable predicates live in
another namespace. Sometimes the Prolog system shyes away from jumping back into Prolog execution while doing an arithmetic evaluation in the host language.
Some Prolog systems have nevertheless user defined evaluable predicates, like ECLiPSe Prolog and Jekejeke Prolog. In Jekejeke Prolog the overhead was two fold. To my surprise in the new Dogelog runtime user definable evaluable
predicates show an advantage:
/* Dogelog Runtime 0.9.5 */
fact(0, 1) :- !.
fact(N, X) :- M is N-1, fact(M, Y), X is Y*N.
fact2(0, 1) :- !.
fact2(N, X) :- X is fact2(N-1)*N.
for(_).
for(N) :- N > 1, M is N - 1, for(M).
% ?- time((for(1000), fact(1000, _), fail; true)).
% % Wall 1595 ms, trim 0 ms
% ?- time((for(1000), _ is fact2(1000), fail; true)).
% % Wall 1394 ms, trim 0 ms
I am attributing the slight speed advantage to the more concise formulation in fact2/2. The formulation uses less Prolog logical variables. And the user defined evaluable predicates capable (is)/2 internally does also no Prolog logical variables, the host language assigments that happen do not allocate
a Prolog logical variable or trail the same, so that in the end there is a speed-up.

Safer type tests in Prolog

ISO-Prolog (ISO/IEC 13211-1:1995 including Cor.1:2007, Cor.2:2012) offers the following built-in predicates for testing the type of a term:
8.3 Type testing
1 var/1. 2 atom/1. 3 integer/1. 4 float/1. 5 atomic/1. 6 compound/1. 7 nonvar/1. 8 number/1. 9 callable/1. 10 ground/1. 11 acyclic_term/1.
Within this group there are those whose purpose is solely to test for a certain instantiation, that is 8.3.1 var/1, 8.3.7 nonvar/1, 8.3.10 ground/1, and those that assume that a term is sufficiently instantiated such that the type test is safe. Unfortunately, they are combined with testing for a concrete instantiation.
Consider the goal integer(X) which fails if X is a nonvar term that is not an integer and when X is a variable. This destroys many desirable declarative properties:
?- X = 1, integer(X).
true.
?- integer(X), X = 1.
false.
Ideally the second query would either succeed using some form of coroutining ; or it would issue an instantiation error1 according to the error classification. After all:
7.12.2 Error classification
Errors are classified according to the form of Error_term:
a) There shall be an Instantiation Error when an
argument or one of its components is a variable, and an
instantiated argument or component is required. It has
the form instantiation_error.
...
Note that this implicit combination of instantiation testing and type testing leads to many errors in Prolog programs and also here on SO.
A quick fix to this situation would be to add an explicit test in front of every test built-in, either verbosely as
( nonvar(T) -> true ; throw(error(instantiation_error,_)) ),
integer(T), ....
or more compactly as
functor(T, _,_),
integer(T), ....
it could be even
T =.. _,
integer(T), ...
My question is twofold:
How to provide this functionality on the user level?
and, to make this also a bit challenging:
What is the most compact implementation of a safer atomic/1 written in ISO-Prolog?
1 Other less desirable options would be to loop or to produce a resource error. Still preferable to an incorrect result.
The testing for types needs to distinguish itself from the traditional "type testing" built-ins that implicitly also test for a sufficient instantiation. So we effectively test only for sufficiently instantiated terms (si). And if they are not sufficiently instantiated, an appropriate error is issued.
For a type nn, there is thus a type testing predicate nn_si/1 with the only error condition
a) If there is a θ and σ such that nn_si(Xθ) is
true and nn_si(Xσ) is false —
instantiation_error.
atom_si(A) :-
functor(A, _, 0), % for the instantiation error
atom(A).
integer_si(I) :-
functor(I, _, 0),
integer(I).
atomic_si(AC) :-
functor(AC,_,0).
list_si(L) :-
\+ \+ length(L, _), % for silent failure
sort(L, _). % for the instantiation error
This is available as library(si) in Scryer.
In SWI, due to its differing behavior in length/2, use rather:
list_si(L) :-
'$skip_list'(_, L, T),
functor(T,_,_),
T == [].
This is a very naive attempt at implementing both your suggested solutions.
First, has_type(Type, Var) that succeeds, or fails with an instantiation error:
has_type(Type, X) :-
var(X), !,
throw(error(instantiation_error, _)).
has_type(Type, X) :-
nonvar_has_type(Type, X).
nonvar_has_type(atom, X) :- atom(X).
nonvar_has_type(integer, X) :- integer(X).
nonvar_has_type(compound, X) :- compound(X).
% etc
Second, a could_be(Type, Var) (analogy to must_be/2) that uses coroutining to allow the query to succeed at some point in the future:
could_be(Type, X) :-
var(X), !,
freeze_type(Type, X).
could_be(Type, X) :-
nonvar_has_type(Type, X).
freeze_type(integer, X) :- freeze(X, integer(X)).
freeze_type(atom, X) :- freeze(X, atom(X)).
freeze_type(compound, X) :- freeze(X, compound(X)).
% etc
There are several weak points to this approach but your comments might help me understand the use cases better.
EDIT: On "types" in Prolog
Types in Prolog, as I understand them, are not "types": they are just information that can be queried at run time, and which exists because it is a useful leaky abstraction of the underlying implementation.
The only way I have been able to make practical use of a "type" has been to "tag" my variables, as in the compound terms number(1), number(pi), operator(+), date(2015, 1, 8), and so on. I can then put variables in there, write deterministic or semi-deterministic predicates, understand what my code means when I see it a week later....
So a free variable and an integer are just terms; mostly because, as your question very smartly points out, a free variable can become an integer, or an atom, or a compound term. You could use coroutining to make sure that a free variable can only become a certain "type" of term later, but this is still inferior to using compound terms, from a practical point of view.
It highly likely that I am confounding very different issues here; and to be honest, my experience with Prolog is limited at best. I just read the documentation of the implementation I am using, and try to find out the best way to use it to my advantage.

Resources