Should I enforce mode declarations by throwing instantiation errors? - prolog

I have been working on some code in which I have predicates that either do not terminate or give incorrect solutions if they are used in certain modes.
Here is an example:
%! list_without_duplicates(+List1, -List2) is det.
%
% True if List2 contains all the elements of List1 but has
% no duplicate elements.
%
% Ex: list_without_duplicates([1,1,2,2,3,3],[1,2,3]).
list_without_duplicates([],[]).
list_without_duplicates([X|Xs],[X|Acc]) :-
\+ memberchk(X,Xs),
list_without_duplicates(Xs,Acc).
list_without_duplicates([X|Xs],Acc) :-
memberchk(X,Xs),
list_without_duplicates(Xs,Acc).
% This is great.
?- list_without_duplicates([1,1,2,2,3,3],X).
X = [1, 2, 3] ;
false.
% This is not great.
list_without_duplicates_(X,[1,2,3]).
ERROR: Stack limit (1.0Gb) exceeded
ERROR: Stack sizes: local: 1Kb, global: 0.8Gb, trail: 0.1Mb
ERROR: Stack depth: 16,586, last-call: 100%, Choice points: 5
...
So my question is, am I better off throwing an error if the first argument is not instantiated?
list_without_duplicates(List1,List2) :-
( var(List1)
-> instantiation_error(List1)
; list_without_duplicates_star(List1,List2)
).
list_without_duplicates_star([],[]).
list_without_duplicates_star([X|Xs],[X|Acc]) :-
\+ memberchk(X,Xs),
list_without_duplicates_star(Xs,Acc).
list_without_duplicates_star([X|Xs],Acc) :-
memberchk(X,Xs),
list_without_duplicates_star(Xs,Acc).
I have been reading through some Prolog libraries such as apply.pl, which on my system is located in /usr/local/logic/lib/swipl/library/apply.pl. Here is code directly from this library. Note that no instantiation errors are mentioned anywhere here.
maplist(Goal, List1, List2) :-
maplist_(List1, List2, Goal).
maplist_([], [], _).
maplist_([Elem1|Tail1], [Elem2|Tail2], Goal) :-
call(Goal, Elem1, Elem2),
maplist_(Tail1, Tail2, Goal).
Yet if I use this predicate like so I get an instantiation error:
?- use_module(library(apply)).
true.
?- apply:maplist(X,[1,2,3],[4,5,6]).
ERROR: Arguments are not sufficiently instantiated
ERROR: In:
ERROR: [11] apply:maplist_([1,2|...],[4,5|...],apply:_5706)
ERROR: [9] toplevel_call(user:apply: ...) at /usr/local/logic/lib/swipl/boot/toplevel.pl:1113
ERROR:
ERROR: Note: some frames are missing due to last-call optimization.
ERROR: Re-run your program in debug mode (:- debug.) to get more detail.
I do not understand how Prolog knows to throw this error.

am I better off throwing an error if the first argument is not instantiated?
In your case not much. In fact, the non-termination you encountered was annoying and resource-wasting but at least not incorrect. I would be more concerned about cases like:
?- Y = b, list_without_duplicates([a,Y],[a,b]).
Y = b
; false. % inefficiency
?- list_without_duplicates([a,Y],[a,b]).
false. % incompleteness
It gets even worse in the presence of constraints.
As a general rule-of-thumb, whenever you want to discern according to instantiations, test for the more instantiated pattern. In your case, do not test with var/1, instead rather use nonvar/1. This focuses your attention on the safer case. And in your case you might have realized that nonvar/1 alone is not enough. In fact, use ground/1:
list_without_duplicates(List1,List2) :-
( ground(List1)
-> list_without_duplicates_star(List1,List2)
; instantiation_error(List1)
).
Consider using iwhen/2 to hide the details; and get an easy upgrade to coroutining: just delete the i and you are using when/2.
In general, instantiation errors are here to mask out procedural problems. Some of them are related to non-termination, and others help to mask-out the non-relational parts of impure code like memberchk/2.
The question then remains, why write impure code in the first place? Even more so if it is quite inefficient as yours? With library(reif) you get a clean, pure and quite efficient solution:
:- use_module(library(reif)).
list_nub([], []).
list_nub([X|Xs], Ys0) :-
if_(memberd_t(X,Xs), Ys0 = Ys1, Ys0 = [X|Ys1]),
list_nub(Xs, Ys1).
Answering #gusbro's remark on performance in SWI, here is the expansion in SICStus Prolog (to get that listing, I declared list_nub/2 dynamic). The expansion should look similar in SWI.
list_nub([], []).
list_nub([A|B], C) :-
memberd_t(A, B, D),
( D==true ->
C=E
; D==false ->
C=[A|E]
; nonvar(D) ->
throw(error(type_error(boolean,D),type_error(call(user:memberd_t(A,B),D),2,boolean,D)))
; throw(error(instantiation_error,instantiation_error(call(user:memberd_t(A,B),D),2)))
),
list_nub(B, E).

I would refrain from directly throwing in your Prolog code unless you are absolutely certain you have no other choice.
Use the built-ins, they provide a lot of "type-checking" for free. Using call with a non-callable is one example. Basically all built-ins check their arguments and if they don't, I would consider this a bug and report it. Examples:
?- between(1, 3, foo).
?- succ(X, 0).
?- X = [_|X], length(X, N).
?- X is 3 - a.
?- X is 3 - A.
?- sort([a,b|c], Sorted).
To rephrase, as long as you find the appropriate built-in to use in your own code, you shouldn't need to throw explicitly.
If you are checking the arguments, go ahead and use library(error).
The "without duplicates" predicate is a perennial classic. You need a very good reason to not use sort/2 for this. If you did use sort/2, you will immediately get an error:
?- sort(X, Y).
ERROR: Arguments are not sufficiently instantiated
If you decide to program it yourself, you might as well go down the rabbit hole and use if_/3 as suggested by #false. As a matter of fact, you might find a fancy solution here on SO if you simply look through the links in the profile of #false.

Related

Simple Prolog program: "Arguments are not sufficiently instantiated" error

I am writing a Prolog predicate that cuts first three elements off a numbered list and prints the result. An example of a numbered list:
[e(f,1),e(o,2),e(o,3),e(b,4),e(a,5),e(r,6)].
The original predicate for normal list looks like this:
strim([H|T],R) :-
append(P,R,[H|T]),
length(P,3).
So, since length predicate works perfectly for numbered lists as well, I only had to write predicate that appends one numbered list to another:
compose([],L,[L]).
compose([e(F,C)|T],e(A,_),[e(F,C)|L]) :-
N is C+1,
compose(T,e(A,N),L).
napp(X,[],X).
napp(L,[e(X,Y)|T],M):-
compose(L,e(X,Y),L1),
napp(L1,T,M).
I expected the predicate for numbered list to be a slightly modified version of predicate for normal list, so I wrote this:
numstrim([e(X,Y)|T],R) :-
napp(P,R,[e(X,Y)|T]),
length(P,3).
However, I'm getting this error:
ERROR: compose/3: Arguments are not sufficiently instantiated
Could somebody please explain what's causing the error and how to avoid it? I'm new to Prolog.
Instantiation errors are a common phenomenon in Prolog programs that use moded predicates: These are predicates that can only be used in special circumstances, requiring for example that some arguments are fully instantiated etc.
As a beginner, you are in my view well advised to use more general predicates instead, so that you can freely exchange the order of goals and do not have to take procedural limitations into account, at least not so early, and without the ability to freely experiment with your code.
For example, in your case, the following trivial change to compose/3 gives you a predicate that works in all directions:
compose([], L, [L]).
compose([e(F,C)|T], e(A,_), [e(F,C)|L]) :-
N #= C+1,
compose(T, e(A,N), L).
Here, I have simply replaced the moded predicate (is)/2 with the CLP(FD) constraint (#=)/2, which completeley subsumes the more low-level predicate over integers.
After this small change (depending on your Prolog system, you may have to import a library to use the more general arithmetic predicates), we get:
?- numstrim([e(f,1),e(o,2),e(o,3),e(b,4),e(a,5),e(r,6)], Es).
nontermination
So, we find out that the instantiation error has actually overshadowed a different problem that can only be understood procedurally, and which has now come to light.
To improve this, I now turn around the two goals of numstrim/2:
numstrim([e(X,Y)|T], R) :-
length(P, 3),
napp(P, R, [e(X,Y)|T]).
This is because length(P, 3) always terminates, and placing a goal that always terminates first can at most improve, never worsen, the termination properties of a pure and monotonic logic program.
So now we get:
?- numstrim([e(f,1),e(o,2),e(o,3),e(b,4),e(a,5),e(r,6)], Es).
Es = [e(b, _1442), e(a, _2678), e(r, _4286)] .
That is, at least we get an answer now!
However, the predicate still does not terminate universally, because we get:
?- numstrim([e(f,1),e(o,2),e(o,3),e(b,4),e(a,5),e(r,6)], Es), false.
nontermination
I leave fixing this as an exercise.

Sorting program for SWI Prolog

Why this program answers False in SWI-PROLOG?
sor(x, y):- sorted(y), perm(x, y).
sorted([]).
sorted([x, []]).
sorted([x, y, z]):- mi(x, y), sorted([y, z]).
perm([], []).
perm([x,y],[u,v]):- delete(u,[x,u],z), perm(z,v).
delete(x,[x,y],y].
delete(x, [y, z], [y, w]):- delete(x,z,w).
mi(0, x).
mi(s(x), s(y)):- mi(x, y).
for the query ?-
sor([s(s(s(s(s(0))))), s(s(s(s(s(s(0)))))), s(s(s(0))), s(s(0)), []], y).
This is an adaptation to SWIProlog of an inefficient sorting-program used as example in the book Foundations of Logic Programming, by Loyd (you can find the original SLOWSORT program example in this pdf, on page 9)
SWI Prolog is a standard Prolog, isn't it?
Edit
Now I have tried to correct the program (looking a little to the lists syntax in Prolog)
sor(X, Y):- perm(X, Y), sorted(Y).
sorted([]).
sorted([X|[]]).
sorted([X|[Y|Z]]):- mi(X, Y), sorted([Y|Z]).
perm([], []).
perm([X|Y],[U|V]):- delete(U,[X|Y],Z), perm(Z, V).
delete(X,[X|Y],Y).
delete(X, [Y|Z], [Y|W]):- delete(X, Z, W).
mi(0, X).
mi(s(X), s(Y)):- mi(X, Y).
and changing the query in
sor([s(s(s(s(s(0)))))|[ s(s(s(s(s(s(0))))))|[s(s(s(0)))|[ s(s(0))|[]]]]], Y).
Well, Prolog now gives success, but it gives this substitution
Y = [s(s(0)), s(s(s(0))), s(s(s(s(s(0))))), s(s(s(s(s(s(...))))))]
and I don't understand the meaning of (...): Why not (0)?
Edit2
I notice that after giving the command swipl -s slowsort.pl I obtain this error message
Warning: /home/navigazione/Scrivania/slowsort.pl:3:
Singleton variables: [X]
Warning: /home/navigazione/Scrivania/slowsort.pl:9:
Singleton variables: [X]
It seems to refer to 3th and 9th rows of the program, but I don't understand what it means.
Great, you managed to translate it to correct Prolog :)
What you see is the top level trying to make things readable by omitting stuff (the ... means there is stuff there that is not shown). See this question and answers for different ways you can tell the top level to show the complete term instead of hiding parts of it.
As for the singleton variable warnings, it just tells you that you have logical variables (on lines 3 and 9) that you have only mentioned once in their syntactical scope. You can write _X instead of X to make it explicit that you are not using the value of the variable in that scope.

Make a predicate reversible

I'm new to prolog; I'm coming from a structured programming background, as will become obvious :)
I am building up a prolog query that involves reversing a number; eg. reverse_num(123,X) results in X = 321. I came up with the following definition, but it only works when I provide a number as the first parameter.
reverse_num(Num, Revnum) :-
number_chars(Num, Atoms),
reverse(Revatoms, Atoms),
number_chars(Reversed, Revatoms),
Reversed = Revnum.
the number_chars/2 predicate doesn't like an unsubstantiated variable if I do: reverse_num(X,123) (where I'm expecting X to be 321).
Am I trying too hard to make reverse_num do something it shouldn't (should it be understood to work only with a number as the first parameter and variable as the second)?
Or is there an easy / straight-forward way to handle a variable as the first parameter?
Relational naming
Before jumping into coding, let's take a step back. After all, the idea in Prolog is to define relations. Your name reverse_num/2 rather suggests some actions, num_reversed/2 might be a better name.
Determine the relation
Your definition is not that bad, let me rewrite it to1:
num_reversed(Num, Reversed) :-
number_chars(Num, Chars),
reverse(Chars, Revchars),
number_chars(Reversed, Revchars).
?- num_reversed(123,X).
X = 321.
?- num_reversed(1230,X).
X = 321.
?- num_reversed(12300,X).
X = 321.
Do you see the pattern? All numbers N*10^I have the same result!
Now, let's ask some more:
?- num_reversed(Num, 321).
error(instantiation_error,number_chars/2).
Hm, what did we expect? Actually, we wanted all 123*10^I to be printed. That's infinitely many solutions. So above query, if correctly answered, would require infinitely many solutions to be printed. If we print them directly, that will take all our universe's lifetime, and more!
It is for this reason, that Prolog produces an instantiation error instead. By this, Prolog essentially states:
This goal is too general that I can make a good answer. Maybe there are infinitely many solutions, maybe not. I know not. But at least I indicate this by issuing an error. To remove this error you need to instantiate the arguments a bit more.
So the answer Prolog produced was not that bad at all! In fact, it is much better to produce a clean error than to, say, fail incorrectly. In general, Prolog's errors are often a very useful hint to what semantic problems you might have. See all error classes how.
Coroutining
As have other answers suggested, coroutining, using when/2 might solve this problem. However, coroutining itself has many semantic problems. Not without reason, systems like XSB do not offer it, due to the many problems related to subsumption checking. An implementation that would be compatible to it would be unexpectedly inefficient.
But for the sake of the point, we could make our definition more versatile by querying it like
?- when(nonvar(Num), num_reversed(Num, Reversed)).
when(nonvar(Num), num_reversed(Num, Reversed)).
Now we get back as an answer exactly the query we entered. This is also known as floundering. So there is a way to represent infinitely may solutions in a compact manner! However, this comes at a rather high price: You no longer know whether a solution exists or not. Think of:
?- when(nonvar(Num), num_reversed(Num, -1)).
when(nonvar(Num), num_reversed(Num, -1)).
Others have suggested to wait also for nonvar(Reversed) which would only be correct if we would produce infinitely many answers - but, as we have seen - this just takes too much time.
Coroutining looked as a very promising road at the beginning of the 1980s. However, it has never really caught on as a general programming methodology. Most of the time you get much too much floundering which is just a pain and even more difficult to handle than, say instantiation errors.
However, a more promising offspring of this development are constraints. There, the mechanisms are much cleaner defined. For practical purposes, programmers will only use existing libraries, like CLPFD, CLPQ, or CHR. Implementing your own library is an extremely non-trivial project in its own right. In fact it might even be possible to provide an implementation of num_reversed/2 using library(clpfd) that is, restricting the relation to the integer case.
Mode dependent conditionals
Traditionally, many such problems are solved by testing for instantiations explicitly. It is good style to perform this exclusively with nonvar/1 and ground/1 like the condition in when/2- other type test predicates lead easily to errors as exemplified by another answer.
num_reversed(Num, Reversed) :-
( nonvar(Num)
-> original_num_reversed(Num, Reversed)
; original_num_reversed(Reversed, Base),
( Base =:= 0
-> Num is 0
; length(_, I),
Num is Base*10^I
)
).
Above code breaks very soon for floats using base 2 and somewhat later for base 10. In fact, with classical base 2 floats, the relation itself does not make much sense.
As for the definition of number_chars/2, ISO/IEC 13211-1:1995 has the following template and mode subclause:
8.16.7.2 Template and modes
number_chars(+number, ?character_list)
number_chars(-number, +character_list)
The first case is when the first argument is instantiated (thus nonvar). The second case, when the first argument is not instantiated. In that case, the second argument has to be instantiated.
Note, however, that due to very similar problems, number_chars/2 is not a relation. As example, Chs = ['0','0'], number_chars(0, Chs) succeeds, whereas number_chars(0, Chs), Chs = ['0','0'] fails.
Very fine print
1 This rewrite is necessary, because in many Prologs reverse/2 only terminates if the first argument is known. And in SWI this rewrite is necessary due to some idiosyncratic inefficiencies.
The number_chars/2 predicate has the signature:
number_chars(?Number, ?CharList)
But although not fully specified by the signature, at least Number or CharList have to be instantiated. That's where the error occurs from.
If you call:
reverse_num(Num,123)
You will call number_chars/2 with both uninstatiated at that time so the predicate will error.
A not very nice solution to the problem is to ask whether Num or RevNum are number/2s. You can do this by writing two versions. It will furthermore filter other calls like reverse_num(f(a),b), etc.:
reverse_num(Num,Revnum) :-
\+ number(Num),
\+ number(Revnum),
throw(error(instantiation_error, _)).
reverse_num(Num, Revnum) :-
ground(Num),
number(Num),
!,
number_chars(Num, Atoms),
reverse(Revatoms, Atoms),
number_chars(Revnum, Revatoms).
reverse_num(Num, Revnum) :-
ground(Revnum),
number(Revnum),
reverse_num(Revnum,Num).
Or you can in case you use two nongrounds (e.g. reverse_num(X,Y).) an instantiation error instead of false as #false says:
reverse_num(Num,Revnum) :-
\+ number(Num),
\+ number(Revnum),
!,
throw(error(instantiation_error, _)).
reverse_num(Num, Revnum) :-
number(Num),
!,
number_chars(Num, Atoms),
reverse(Revatoms, Atoms),
number_chars(Revnum, Revatoms).
reverse_num(Num, Revnum) :-
reverse_num(Revnum,Num).
The cut (!) is not behaviorally necessary, but will increase performance a bit. I'm not really a fan of this implementation, but Prolog cannot always fully make predicates reversible since (a) reversibility is an undecidable property because Prolog is Turing complete; and (b) one of the characteristics of Prolog is that the body atoms are evaluated left-to-right. otherwise it will take ages to evaluate some programs. There are logic engines that can do this in an arbitrary order and thus will succeed for this task.
If the predicate/2 is commutative, a solution that can be generalized is the following pattern:
predicate(X,Y) :-
predicate1(X,A),
predicate2(A,B),
% ...
predicaten(C,Y).
predicate(X,Y) :-
predicate(Y,X).
But you cannot simply add the last clause to the theory, because it can loop infinitely.
Nice to see someone is also worried about define flexible rules with no restrictions in the set of bound arguments.
If using a Prolog system that supports coroutining and the when/2 built-in predicate (e.g. SICStus Prolog, SWI-Prolog, or YAP), try as:
reverse_num(Num, Reversed) :-
when( ( ground(Num); ground(Atoms) ), number_chars(Num, Atoms) ),
when( ( ground(Reversed); ground(Revatoms) ), number_chars(Reversed, Revatoms) ),
reverse(Atoms , Revatoms).
that gives:
?- reverse_num( 123, X ).
X = 321.
?- reverse_num( X, 123 ).
X = 321 .
( thanks to persons who provided theses answers: Prolog: missing feature? )
This SWISH session shows my effort to answer.
Then I've come back here, where I found I was on #PasabaPorAqui' mood (+1), but I didn't get it right.
But, such an interesting topic: notice how regular is the join pattern.
reverse_num(X, Y) :-
when((nonvar(Xs);nonvar(Ys)), reverse(Xs, Ys)),
when((nonvar(X) ;nonvar(Xs)), atomic_chars(X, Xs)),
when((nonvar(Y) ;nonvar(Ys)), atomic_chars(Y, Ys)).
So, we can generalize in a simple way (after accounting for PasabaPorAqui correction, ground/1 it's the key):
% generalized... thanks Pasaba Por Aqui
:- meta_predicate when_2(0).
when_2(P) :-
strip_module(P,_,Q),
Q =.. [_,A0,A1],
when((ground(A0);ground(A1)), P).
reverse_num(X, Y) :-
maplist(when_2, [reverse(Xs, Ys), atomic_chars(X, Xs), atomic_chars(Y, Ys)]).
I think I understand why nonvar/1 was problematic: the list bound for reverse get 'fired' too early, when just the head get bound... too fast !
maplist/2 is not really necessary: by hand we can write
reverse_num(X, Y) :-
when_2(reverse(Xs, Ys)),
when_2(atomic_chars(X, Xs)),
when_2(atomic_chars(Y, Ys)).
this seems an ideal application of term rewriting... what do you think about -:- ? Implementing that we could write bidirectional code like
reverse_num(X, Y) -:-
reverse(Xs, Ys),
atomic_chars(X, Xs),
atomic_chars(Y, Ys).
edit SWISH maybe is not 'term_rewrite' friendly... so here is a lower level approach:
:- op(900, xfy, ++).
A ++ B ++ C :- when_2(A), B ++ C.
A ++ B :- when_2(A), when_2(B).
reverse_num(X, Y) :-
reverse(Xs, Ys) ++ atomic_chars(X, Xs) ++ atomic_chars(Y, Ys).
Setting aside the problem of trailing zeroes turning into leading zeroes, it doesn't seem like it should be much more complicated than something like this (made somewhat more complicated by dealing with negative numbers):
reverse_number(X,Y) :- number(X) , ! , rev(X,Y) .
reverse_number(X,Y) :- number(Y) , ! , rev(Y,X) .
rev(N,R) :-
N < 0 ,
! ,
A is abs(N) ,
rev(A,T) ,
R is - T
.
rev(N,R) :-
number_chars(N,Ns) ,
reverse(Ns,Rs) ,
number_chars(R,Rs)
.
Note that this does require at least one of the arguments to reverse_number/2 to be instantiated.

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.

How to find facts that do not have contribution in goal

I'm trying to write a program that can check if the student program can fulfill a certain goal or not. I can do that part. Now, I want to check if the student program actually contains unnecessary code or not. For solving this case, I think I need to know if the student program contains facts that do not contribute to the specified goal. However, I cannot figure it out, how to find facts that do not contribute to the goal.
To make it easier to understand, let's consider a simpler example. In this example, the specified goal is: is john the grandfather of tomy?
father(john, jim).
father(jim, tomy).
father(john, david).
father(bruce, anne).
mother(mary, jim).
grandfather(A,B) :- father(A, X), father(X,B).
goal:- grandfather(john, tomy).
Actually the goal can be satisfied by the following facts only:
father(john, jim).
father(jim, tomy).
And the things that I want to know is which facts that actually do not contribute to the goal. The answer would be all the following facts:
father(john, david).
father(bruce, anne).
mother(mary, jim).
Any help is really appreciated.
Thanks
Your question cannot be directly answered in Prolog, but you can answer it manually by using a failure-slice. Simply add false goals into your program and always test whether goal still succeeds. Here is the minimal program I obtained.
father(john, jim).
father(jim, tomy).
father(john, david) :- false.
father(bruce, anne) :- false.
mother(mary, jim) :- false.
grandfather(A,B) :- father(A, X), father(X,B).
goal:- grandfather(john, tomy).
Every time you insert a goal false into a pure, monotonic program, you know for sure that the set of solutions is reduced (or stays the same). So finding such a slice involves about as many trials as there are places to set such goals. Sometimes you might want to add goals X = term to narrow down the program even further.
Failure slices are particularly useful when you want to understand the termination properties of a program, see failure-slice for more.
Unbelievably, there is a partial solution to this problem here. To reproduce the relevant portion here is substantial code, so let me make it clear that this is not my own work, I am just including the work here in case the website above goes missing in the future.
First, you need a meta-circular interpreter:
mi_circ(true).
mi_circ((A,B)) :-
mi_circ(A),
mi_circ(B).
mi_circ(clause(A,B)) :-
clause(A,B).
mi_circ(A \= B) :-
A \= B.
mi_circ(G) :-
G \= true,
G \= (_,_),
G \= (_\=_),
G \= clause(_,_),
clause(G, Body),
mi_circ(Body).
This works for \=/2 and clause/2. To generalize this pattern to all built-in predicates, we can use predicate_property/2 to identify them as such for calling them directly:
provable(true, _) :- !.
provable((G1,G2), Defs) :- !,
provable(G1, Defs),
provable(G2, Defs).
provable(BI, _) :-
predicate_property(BI, built_in),
!,
call(BI).
provable(Goal, Defs) :-
member(Def, Defs),
copy_term(Def, Goal-Body),
provable(Body, Defs).
This gives you a reified meta-interpreter, meaning you can pass provable/2 a goal and a set of definitions and it will tell you whether the definitions supplied are sufficient to prove the goal. I bet you can taste how close we are to the final solution now!
With the following additional definitions, we can use this MI to identify redundant facts in some predicate definitions:
redundant(Functor/Arity, Reds) :-
functor(Term, Functor, Arity),
findall(Term-Body, clause(Term, Body), Defs),
setof(Red, Defs^redundant_(Defs, Red), Reds).
redundant_(Defs, Fact) :-
select(Fact-true, Defs, Rest),
once(provable(Fact, Rest)).
This is using select/3 to portion out one definition at a time and see if the predicate is still provable. By doing that across all the definitions you can get the set of all unnecessary rules.
Given the definitions:
as([]).
as([a]). % redundant
as([a,a]). % redundant
as([A|As]) :-
A = a, % test built-in =/2
5 is 2 + 3, % test built-in is/2
1 > 0, % test built-in >/2
as(As).
we can ask for facts which are deducible from all (respective) remaining clauses and hence redundant:
?- redundant(as/1, Reds).
Reds = [as([a]), as([a, a])]
Alas, this does not work out-of-the-box on your problem, but I do think that with some study you could find a way to apply this technique to it and come up with something. For instance, you could create a meta-interpreter that takes a list of facts to check and perform the same sort of remove-one-then-prove loop to find them.
Hope this helps and is at least interesting.
Another option is to modify and use a unit testing framework that does predicate clause coverage. Define a unit test with the goal for which you want to find out which clauses don't contribute to it. The modifying bit, if necessary, will be to modify the coverage report to also identify those clauses. Just as an example of what I mean, in case it's not clear, consider the following output of the Logtalk lgtunit tool using one of the examples in the Logtalk distribution:
?- {ack(tester)}.
%
% tests started at 2013/6/5, 19:54:9
% running tests from object tests
% file: /Users/pmoura/logtalk/examples/ack/tests.lgt
% ack_1: success
% ack_2: success
% ack_3: success
% 3 tests: 0 skipped, 3 passed, 0 failed
% completed tests from object tests
% ack: ack/3 - [1,2,3] (3/3)
% 1 unit declared in the test file containing 3 clauses
% 1 unit covered containing 3 clauses
% 3 out of 3 clauses covered, 100,000000% coverage
% tests ended at 2013/6/5, 19:54:9
%
true.
The line:
% ack: ack/3 - [1,2,3] (3/3)
shows which clauses were used by the three unit tests for the ack/3 predicate.

Resources