I am trying to combine some pure predicates from previous stack overflow questions to make my own predicate.
I want to give a list of c's (which have associated facts -'ats' with them) and a 'feature' term which has an operator and a threshold for an 'at' . I want to partition the lists of c's, if the c does not have the corresponding 'at' from the 'feature' it will go in the false partition, otherwise the operator will test the 'at' for that 'c' and splits the c's appropriately.
For example:
?-cpgpartition_ts_fs_feature([c1,c2,c3],Ts,Fs,feature(at2,_,>=,10)).
Should result in :
Ts = [c3], %c3 has an at2 >= 10
Fs = [c1,c2]. %c1 has at2 <10 and c2 does not have an at2
This is the code I have:
:-use_module(library(clpfd)).
cpgpartition_ts_fs_feature([],[],[],_).
cpgpartition_ts_fs_feature([X|Xs0],Ts,Fs,Feature):-
Feature = feature(At,_,Op,FValue),
cpg_ats_i(X,AtList),
atom_concat(#,Op,Op2), %make clpfd operator
Test =..[Op2,AtValue3,FValue],
if_(memberd_t(attribute(At,AtValue3),AtList),
(
if_(call(Test), (Ts=[X|Ts0],Fs=Fs0),
( Ts =Ts0,Fs=[X|Fs0]))
)
,Fs=[X|Fs0]),
cpgpartition_ts_fs_feature(Xs0,Ts0,Fs0,Feature).
if_(If_1, Then_0, Else_0) :-
call(If_1, T),
( T == true -> call(Then_0)
; T == false -> call(Else_0)
; nonvar(T) -> throw(error(type_error(boolean,T),_))
; /* var(T) */ throw(error(instantiation_error,_))
).
bool01_t(1,true).
bool01_t(0,false).
=(X, Y, T) :-
( X == Y -> T = true
; X \= Y -> T = false
; T = true, X = Y
; T = false,
dif(X, Y) % ISO extension
% throw(error(instantiation_error,_)) % ISO strict
).
#=<(X,Y,Truth) :- X #=< Y #<==> B, bool01_t(B,Truth).
#<( X,Y,Truth) :- X #< Y #<==> B, bool01_t(B,Truth).
#>( X,Y,Truth) :- X #> Y #<==> B, bool01_t(B,Truth).
#>=(X,Y,Truth) :- X #>= Y #<==> B, bool01_t(B,Truth).
list_memberd_t([] ,_,false).
list_memberd_t([Y|Ys],X,Truth) :-
if_(X=Y, Truth=true, list_memberd_t(Ys,X,Truth)).
list_memberd_truth(Xs,X,Truth) :- list_memberd_t(Xs,X,Truth).
memberd_t(X,Xs,Truth) :- list_memberd_t(Xs,X,Truth).
value_intvalue(attribute(_A,X),attribute(_A,Y)):-
AtValue2 is X *100, %Convert decimal number to integer.
Y is integer(AtValue2).
cpg_ats_i(C,AtList):-
cpg_ats(C,Ats),
maplist(value_intvalue,Ats,AtList).
cpg_ats(c1,[attribute(at1,0.5),attribute(at2,0.03)]).
cpg_ats(c2,[attribute(at1,0.02)]).
cpg_ats(c3,[attribute(at2,0.1),attribute(at3,0.04),attribute(at4,0.08)]).
When trying the test query I get:
cpgpartition_ts_fs_feature([c1,c2,c3],Ts,Fs,feature(at2,_,>=,10)).
Fs = [c1, c2] ;
Fs = [c1, c2, c3] ;
Fs = [c1, c2] ;
Fs = [c1, c2, c3].
And interestingly the results change if the order of the clist is different.
?- cpgpartition_ts_fs_feature([c3,c1,c2],Ts,Fs,feature(at2,_,>=,10)).
Ts = [c3|_12950],
Fs = [c1, c2] ;
Ts = [c3|_12950],
Fs = [c1, c2] ;
Fs = [c3, c1, c2] ;
Fs = [c3, c1, c2].
I think this is because the following query returns results with dif/2
constraints which seem inappropriate for what I am trying to do, I only want the concrete solutions.
?- cpg_ats_i(C,Ats), if_(memberd_t(attribute(at2,AtValue),Ats),Q=true,Q=false).
C = c1,
Ats = [attribute(at1, 50), attribute(at2, 3)],
AtValue = 3,
Q = true ;
C = c1,
Ats = [attribute(at1, 50), attribute(at2, 3)],
Q = false,
dif(AtValue, 3) ;
C = c2,
Ats = [attribute(at1, 2)],
Q = false ;
C = c3,
Ats = [attribute(at2, 10), attribute(at3, 4), attribute(at4, 8)],
AtValue = 10,
Q = true ;
C = c3,
Ats = [attribute(at2, 10), attribute(at3, 4), attribute(at4, 8)],
Q = false,
dif(AtValue, 10).
Also the aim is for this code to run on a large set of data, the c's list will be hundreds of thousands in length and each c might have 50k of ats, how can I work out the memory requirements? and is a different approach using impure predicates likely to take less memory?
As you mentioned the problem is in the dif(X,Y) line in the definition of:
=(X, Y, T) :-
( X == Y -> T = true
; X \= Y -> T = false
; T = true, X = Y
; T = false,
dif(X, Y) % ISO extension
% throw(error(instantiation_error,_)) % ISO strict
).
that's because if you try:
memberd_t(attribute(at2,X),[attribute(at1,0.5),attribute(at2,0.03)],T).
X = 0.03,
T = true ;
T = false,
dif(X, 0.03).
Here the choice point that gives the solution: T = false,dif(X, 0.03).
will lead to execute the part Fs=[X|Fs0]
of the:
if_(memberd_t(attribute(At,AtValue3),AtList),
(
if_(call(Test), (Ts=[X|Ts0],Fs=Fs0),
( Ts =Ts0,Fs=[X|Fs0]))
)
,Fs=[X|Fs0]),
Also this is not right response since if you have attribute(at2,0.03) in the Atlist
you expect memberd_t
to return X = 0.03, T = true
which will trigger the Then_0
part of if_/3
(and no other solution with T = false that will lead to other choice points executing Else_0 part).
So you could remove the T = false,dif(X, Y)
of =/3
and now let's try:
?- cpgpartition_ts_fs_feature([c1,c2,c3],Ts,Fs,feature(at2,_,>=,10)).
Fs = [c1, c2].
good but where is Ts??
So there is another bug:
The above says that it succeeds for Fs = [c1,c2]
and for every Ts. That's because executing Else_0
part of if_/3
which fulfills the Fs
list you don't restrict Ts
list just leave as Ts
and later call cpgpartition_ts_fs_feature(Xs0,Ts0,Fs0,Feature)
with another Ts0
list independent of Ts. So add:
if_(memberd_t(attribute(At,AtValue3),AtList),
(
if_(call(Test), (Ts=[X|Ts0],Fs=Fs0), (Ts =Ts0,Fs=[X|Fs0]))
)
,(Fs=[X|Fs0], Ts = Ts0 )),
^^^^^^^^
here added
Finally I as recommended by @false it is better replace Test =..[Op2,AtValue3,FValue], ..., call(Test)
by call(Op2,AtValue3,FValue)
since call/N
is part of ISO and it fits into the original Mycroft O'Keefe type system.
Now let's try again:
?- cpgpartition_ts_fs_feature([c1,c2,c3],Ts,Fs,feature(at2,_,>=,10)).
Ts = [c3],
Fs = [c1, c2].
Seems right and deterministic :) !!.
As for the memory part of your question I'm not so sure but prefer deterministic predicates that don't leave choice points for memory efficiency. Using pure predicates will make you program more relational and will have better behavior but I'm not so sure if if_/3
is so memory efficient since it contains many calls but I'm not sure maybe someone else could answer this part more clearly.