trans_set(b(Expr,Type,_Infos),Pred) :- % format(user_output,' set --> ~w~n',[Expr]),
(is_set(Type,BaseType)
-> (Expr = identifier(ID) -> NExpr=identifier(ID,BaseType) ; NExpr = Expr)
; add_b2asp_error('Type of expression is not a set: ',Type), fail
),
!,
trans_set(NExpr,Pred).
trans_set(empty_set,Pred) :- !,
DummyArg = 0, % Clingo does not like unbound variables in head??
gensym_if_necessary(empty,Pred),
gen_clingo_clause(Pred,[DummyArg], 1=2 ).
trans_set(bool_set,Pred) :- !,
trans_set(set_extension([pred_false,pred_true]),Pred).
trans_set(value(V),Pred) :- V==[], !, trans_set(empty_set,Pred).
trans_set(value(AVL),Pred) :-
custom_explicit_sets:expand_custom_set_to_list_now(AVL,L),!, % this creates Value list not set_extension list ! TODO
trans_set(set_extension(L),Pred).
trans_set(sequence_extension(L),Pred) :- !,
add_indices(L,1,Set),
trans_set(set_extension(Set),Pred).
trans_set(set_extension(L),Pred) :- !,
gensym_if_necessary(set_ext,Pred),
maplist(trans_scalar4map(Pred),L).
trans_set(union(A,B),Pred) :- !,
trans_set(A,P1),
trans_set(B,P2),
gen_clingo_pred_clause(union,Pred,[X], (call(P1,X)) ),
gen_clingo_clause(Pred,[X], (call(P2,X)) ).
trans_set(intersection(A,B),Pred) :- !,
trans_set(A,P1),
trans_set(B,P2),
gen_clingo_pred_clause(inter,Pred,[X], (call(P1,X),call(P2,X)) ).
trans_set(set_subtraction(A,B),Pred) :- !, % difference set in B
trans_set(A,P1),
trans_set(B,P2),
gen_clingo_pred_clause(diff,Pred,[X], (call(P1,X),not(call(P2,X))) ). % Pred(X) :- P1(X), not P2(X).
trans_set(cartesian_product(A,B),Pred) :- !,
trans_set(A,P1),
trans_set(B,P2),
gen_clingo_pred_clause(cart,Pred,[(X,Y)], (call(P1,X),call(P2,Y)) ). % Pred((X,Y)) :- P1(X), P2(Y).
trans_set(domain(A),Pred) :- !,
trans_set(A,P1),
gen_clingo_pred_clause(domain,Pred,[X], call(P1,(X,_)) ). % Pred(X) :- P1((X,_)).
trans_set(range(A),Pred) :- !,
trans_set(A,P1),
gen_clingo_pred_clause(range,Pred,[X], call(P1,(_,X)) ). % Pred(X) :- P1((_,X)).
trans_set(image(Rel,Set),Pred) :- !, % relational image B operator
trans_set(Rel,P1),
trans_set(Set,P2),
gen_clingo_pred_clause(image,Pred,[Y], (call(P2,X),call(P1,(X,Y))) ). % Pred(Y) :- P1(X), P2((X,Y)).
trans_set(domain_restriction(Set,Rel),Pred) :- !, % domain restriction B operator Set <| Rel
trans_set(Set,P1),
trans_set(Rel,P2),
gen_clingo_pred_clause(dres,Pred,[(X,Y)], (call(P1,X),call(P2,(X,Y))) ). % Pred((X,Y)) :- P1(X), P2((X,Y)).
trans_set(domain_subtraction(Set,Rel),Pred) :- !, % domain subtraction B operator Set <<| Rel
trans_set(Set,P1),
trans_set(Rel,P2),
gen_clingo_pred_clause(dsub,Pred,[(X,Y)], (call(P2,(X,Y)),not(call(P1,X))) ). % Pred((X,Y)) :- P2((X,Y)), not P(X).
trans_set(range_restriction(Rel,Set),Pred) :- !, % range restriction B operator Rel |> Set
trans_set(Set,P1),
trans_set(Rel,P2),
gen_clingo_pred_clause(rres,Pred,[(X,Y)], (call(P1,Y),call(P2,(X,Y))) ). % Pred((X,Y)) :- P1(Y), P2((X,Y)).
trans_set(range_subtraction(Rel,Set),Pred) :- !, % range subtraction B operator Rel |>> Set
trans_set(Set,P1),
trans_set(Rel,P2),
gen_clingo_pred_clause(rsub,Pred,[(X,Y)], (call(P2,(X,Y)), not(call(P1,Y))) ). % Pred((X,Y)) :- P2((X,Y)), not P1(Y).
trans_set(composition(A,B),Pred) :- !, % relational composition operator
trans_set(A,P1),
trans_set(B,P2),
gen_clingo_pred_clause(comp,Pred,[(X,Z)], (call(P1,(X,Y)),call(P2,(Y,Z))) ). % Pred((X,Z)) :- P1((X,Y)), P2((Y,Z)).
trans_set(closure(A),Pred) :- !, % closure1 transitive operator
trans_set(A,P1),
gen_clingo_pred_clause(closure1,Pred,[(X,Y)], call(P1,(X,Y)) ), % Pred((X,Y)) :- P1((X,Y)).
gen_clingo_clause(Pred,[(X,Z)], ( call(P1,(X,Y)) , call(Pred,(Y,Z))) ). % Pred((X,Z)) :- P1((X,Y)), Pred((Y,Z)).
trans_set(overwrite(A,B),Pred) :- !, % relational override operator
trans_set(A,P1),
trans_set(B,P2),
trans_set(domain(B),P3), % we need to create a separate domain encoding to be able to use it inside the "not" below
gen_clingo_pred_clause(overwr,Pred,[(X,Y)], call(P2,(X,Y)) ), % Pred((X,Y)) :- P2((X,Y)).
gen_clingo_clause(Pred,[(X,Y)], (call(P1,(X,Y)),not(call(P3,X))) ). % Pred((X,Y)) :- P1((X,Y)), not P3(X).
trans_set(identity(A),Pred) :- !, % identity operator
trans_set(A,P1),
gen_clingo_pred_clause(id,Pred,[(X,X)], call(P1,X) ). % Pred((X,X)) :- P1(X).
trans_set(reverse(A),Pred) :- !, % reverse B operator r~
trans_set(A,P1),
gen_clingo_pred_clause(rev,Pred,[(Y,X)], (call(P1,(X,Y)))). % Pred((Y,X)) :- P1((X,Y)).
trans_set(interval(A,B),Pred) :- !,
translate_scalar(A,X1,C1),
translate_scalar(B,X2,C2),
gen_clingo_pred_clause(interval,Pred,[X], (C1,C2,'='(X,'..'(X1,X2))) ).
trans_set(global(ID),Pred) :- % B value for entire global enumerated/deferred set ID
b_get_fd_type_bounds(ID,Low,Up),!,
trans_set(interval(Low,Up),Pred).
trans_set(identifier(ID,global(ID)),Pred) :- % TODO: proper checking of scoping
b_get_fd_type_bounds(ID,Low,Up),!,
trans_set(interval(Low,Up),Pred).
trans_set(identifier(ID,BaseType),Pred) :- !,
gen_clingo_set_identifier(ID,BaseType,Pred).
trans_set(X,Pred) :- %write(user_error,X),nl(user_error),
add_b2asp_error('Unsupported set: ',X), Pred=fail.