How to block a target for a list of variables?

My ultimate goal is to create a modified version of automaton / 3 that freezes if there are any variables in the sequence passed to it. those. I do not want the machine to create variables.

(fd_length / 3, if_ / 3, etc., as defined by other people here).

For starters, I have a proven 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 to do this to work on a list of variables so that Goal is called only once, when all the vars have been created?

In this method, if I have more than one variable, I can get behavior that 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 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).

What works:

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

, automaton/3. - automaton/3, , - . .. , .

, :

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

, , X.

?- 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 , , , , , , @Mat, , . .

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)).
+4
3

, Prolog. . , , , . freeze/2, when/2.

, .

, , , . " ", , " ". , , .

. reified, , reification . , , . , (reified) . , . , , . , , . , , , ; .

, , - , , . , , , , , .

. .

reifiy automaton/3. , , , , . , , , , , .

automaton/3, , . , 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(_)).

, , T .

:

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

:

?- seq([X,1], T).

(): , .

:

?- seq([X,1], T), X = 3.
X = 3,
T = 0.

, reified automaton/3 . , reifying - , , T=0 .

:

?- seq([1,1], T), indomain(T).
T = 0 ;
T = 1.

-! ? , ? , , . call_residue_vars/2, .

:

?- call_residue_vars(seq([1,1],0), Vs).

, :

_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

, , , , , , .

, . :

finite(V) :-
        fd_dom(V, L..U),
        dif(L, inf),
        dif(U, sup).

( CLP (FD)) label_fixpoint/1 , :

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

, , .. :

?- call_residue_vars(seq([1,1],0), Vs), <label subset of Vs>.

call_residue_vars/2 , , CLP (FD), .

, - , .

, , . :

tuples_in([[_G1487,1,_G1496]], [[0,0,0],[0,1,1],[1,0,0],[1,1,2],[2,0,2],[2,1,2]])#<==>_G1518

. , , , , .. seq([1,1],0), ?

, :

  • .
  • , .
  • CLP (FD) , , , .
  • labeling/2 , , .
  • , call_residue_vars/2.
  • , .

. , , call_residue_vars/2 .

+4

prolog-coroutining when/2 ( . SICStus Prolog when/2).

, freeze/2 :

freeze(V,Goal) :-
   when(nonvar(V),Goal).
+2

, , :

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

, .

@mat call_residue_vars/2!

+1

Source: https://habr.com/ru/post/1611633/


All Articles