z_translate2(falsity, falsity) :- !.
z_translate2(truth, truth) :- !.
z_translate2(forall(BodyTi, ZConsequent), forall(Ids, Lhs, Rhs)) :-
!, schema_to_typed_identifiers(BodyTi,Ids,Lhs),
z_translate(ZConsequent,Rhs).
z_translate2(exists(BodyTi, ZCondition), exists(Ids, BCondition)) :-
!, schema_to_typed_identifiers(BodyTi,Ids,Condition1),
z_translate(ZCondition,Rhs),
conjunct_predicates([Condition1,Rhs],BCondition).
z_translate2(lambda(BodyTi, ZExpr), lambda(Ids, Lhs, Rhs)) :-
!, schema_to_typed_identifiers(BodyTi,Ids,Lhs),
z_translate(ZExpr,Rhs).
z_translate2(ref(name('\\emptyset',''),[]),empty_set) :- !.
z_translate2(ref(name('\\nat',''),[]),integer_set('NATURAL')) :- !.
z_translate2(ref(name('\\nat','_1'),[]),integer_set('NATURAL1')) :- !.
z_translate2(ref(name('\\num',''),[]),integer_set('INTEGER')) :- !.
z_translate2(ref(Name,[]), identifier(Id)) :-
!,z_translate_identifier(Name, Id).
z_translate2(inop(name('\\extract',''), Za, Zb), compaction(DomRes)) :-
!, create_texpr(domain_restriction(Ba,Bb),BType,[],DomRes),
z_translate(Za,Ba),z_translate(Zb,Bb),
get_texpr_type(Bb,BType).
z_translate2(inop(name('\\filter',''), Za, Zb), compaction(RanRes)) :-
!, create_texpr(range_restriction(Ba,Bb),BType,[],RanRes),
z_translate(Za,Ba),z_translate(Zb,Bb),
get_texpr_type(Ba,BType).
z_translate2(apply(Iteration,ZRel), Result) :-
% iteration of relations. The problem of this operator is that
% it can have negative arguments in Z but not in B
ti_expr(Iteration, apply(Ref,ZN)),
ti_expr(Ref, ref(name(iter,''),[])),
!, z_translate(ZN,BN), z_translate(ZRel,BRel),
get_texpr_type(BRel,BRelType),
create_texpr(reverse(BRel),BRelType,[],Inverse),
( is_a_number(ZN,Value), Value >= 0 ->
% R^x, where x is a non-negative number, we can use it directly
Result = iteration(BRel,BN)
; is_a_negative_number(ZN,Value), Value >= 0 ->
% R^-x, where x is a non-negative number, we can rewrite it into (R~)^x
create_texpr(integer(Value),integer,[],Negation),
Result = iteration(Inverse,Negation)
;
% R^x, where x is an arbitrary expression, we surround it by if-then-else
% to negate the x if necessary
create_texpr(integer(0),integer,[],Zero),
create_texpr(less_equal(Zero,BN),pred,[],NonNegative),
create_texpr(iteration(BRel,BN),BRelType,[],Then),
create_texpr(unary_minus(BN),integer,[],Negation),
create_texpr(iteration(Inverse,Negation),BRelType,[],Else),
Result = if_then_else(NonNegative,Then,Else)).
z_translate2(inop(ZopName, Za, Zb), BBinOp) :-
z_translate_identifier(ZopName,Zop),
is_binary_op(Zop),!,
z_translate_binary_op(Zop,Za,Zb,BBinOp).
z_translate2(inrel(ZopName, Za, Zb), BBinOp) :-
z_translate_identifier(ZopName,Zop),
is_binary_op(Zop),!,
z_translate_binary_op(Zop,Za,Zb,BBinOp).
z_translate2(ingen(ZopName, Za, Zb), BBinOp) :-
z_translate_identifier(ZopName,Zop),
is_binary_op(Zop),!,
z_translate_binary_op(Zop,Za,Zb,BBinOp).
z_translate2(number(Value), integer(Value)) :- !.
z_translate2(ext(ZEntities), set_extension(BEntities)) :-
!, z_translate(ZEntities, BEntities).
z_translate2(seq(ZEntities), sequence_extension(BEntities)) :-
!, z_translate(ZEntities, BEntities).
z_translate2(apply(Items,ZExpr), bag_items(BExpr)) :-
ti_expr(Items,ref(name('items',''),[])),!,
z_translate(ZExpr,BExpr).
z_translate2(apply(ZFun, Zarg), BExpr) :-
ti_expr(ZFun,ref(Name,[])),
z_translate_identifier(Name,Op),
is_unary_op(Op),!,
z_translate_unary_op(Op,Zarg,BExpr).
z_translate2(apply(ZFun, ZArg), function(BFun,BArg)) :-
!, z_translate(ZFun,BFun), z_translate(ZArg,BArg).
z_translate2(postop(Name, Zarg), BExpr) :-
z_translate_identifier(Name,Op),
is_unary_op(Op),!,
z_translate_unary_op(Op,Zarg,BExpr).
z_translate2(prerel(Name, Zarg), BExpr) :-
z_translate_identifier(Name,Op),
is_unary_op(Op),!,
z_translate_unary_op(Op,Zarg,BExpr).
z_translate2(pregen(Name, Zarg), BExpr) :-
z_translate_identifier(Name,Op),
is_unary_op(Op),!,
z_translate_unary_op(Op,Zarg,BExpr).
z_translate2(inrel(name('\\prefix',''), Za, Zb), BExpr) :-
!,z_translate(Za,Ba),z_translate(Zb,Bb),
get_texpr_type(Ba,SeqType),
create_texpr(size(Ba),integer,[],SizeA),
create_texpr(size(Bb),integer,[],SizeB),
create_texpr(greater_equal(SizeB,SizeA),pred,[],GreaterEqual),
create_texpr(restrict_front(Bb,SizeA),SeqType,[],Prefix),
create_texpr(equal(Ba,Prefix),pred,[],Equal),
conjunct_predicates([GreaterEqual,Equal],TypedBExpr),
get_texpr_expr(TypedBExpr,BExpr).
z_translate2(inrel(name('\\suffix',''), Za, Zb), BExpr) :-
!,z_translate(Za,Ba),z_translate(Zb,Bb),
get_texpr_type(Ba,SeqType),
create_texpr(size(Ba),integer,[],SizeA),
create_texpr(size(Bb),integer,[],SizeB),
create_texpr(greater_equal(SizeB,SizeA),pred,[],GreaterEqual),
create_texpr(minus(SizeB,SizeA),integer,[],Diff),
create_texpr(restrict_tail(Bb,Diff),SeqType,[],Suffix),
create_texpr(equal(Ba,Suffix),pred,[],Equal),
conjunct_predicates([GreaterEqual,Equal],TypedBExpr),
get_texpr_expr(TypedBExpr,BExpr).
z_translate2(inrel(name('\\inseq',''), Za, Zb), BExpr) :-
!, create_in_sequence(Za,Zb,BExpr).
z_translate2(prerel(name('\\disjoint',''), Z), BExpr) :-
!, z_translate(Z,B), create_disjoint(B,BExpr).
z_translate2(inrel(name('\\partition',''), Za, Zb), partition(BSet,BSeq)) :-
ti_expr(Za,seq(ZSeq)),!,
z_translate(Zb,BSet),
z_translate(ZSeq,BSeq).
z_translate2(inrel(name('\\partition',''), Za, Zb), BExpr) :-
!, create_partition(Za,Zb,BExpr).
z_translate2(select(ZRecord, ZField), record_field(BRecord, FieldIdentifier)) :-
!, z_translate(ZRecord, BRecord),
z_translate_identifier(ZField, FieldIdentifier).
z_translate2(comp(Body, Nothing),Res) :-
!,
( ti_expr(Nothing,nothing) -> true
;
add_error(proz,'Encountered comprehension set with expression in translation. Should have been replaced.'),
fail),
ti_expr(Body,body(Decls,ZWheres)),
varlist_of_expanded_decls(Decls, Vars, Types),
z_translate_typed_identifiers(Vars,Types,[],Ids),
z_translate(ZWheres,Wheres),
conjunct_predicates(Wheres,Lhs),
%print(comp(Ids,Lhs)),nl,
(is_symbolic_set_comprehension(Ids,Lhs)
-> Res = symbolic_comprehension_set(Ids, Lhs) %,print(symbolic(Ids)),nl
; Res = comprehension_set(Ids, Lhs)).
z_translate2(cross([Za,Zb]), cartesian_product(Ba,Bb)) :-
!, z_translate(Za,Ba), z_translate(Zb,Bb).
z_translate2(cross([ZExpr|ZRest]), cartesian_product(BExpr,TBRest)) :-
!, z_translate(ZExpr,BExpr), z_translate2(cross(ZRest),BRest),
BRest=cartesian_product(BL,BR),get_texpr_type(BL,set(LType)),get_texpr_type(BR,set(RType)),
create_texpr(BRest,set(couple(LType,RType)),[],TBRest).
z_translate2(tuple([Za,Zb]), couple(Ba,Bb)) :-
!, z_translate(Za,Ba), z_translate(Zb,Bb).
z_translate2(tuple([ZExpr|ZRest]), couple(BExpr,TBRest)) :-
!, z_translate(ZExpr,BExpr), z_translate2(tuple(ZRest),BRest),
BRest=couple(BL,BR),get_texpr_type(BL,LType),get_texpr_type(BR,RType),
create_texpr(BRest,couple(LType,RType),[],TBRest).
z_translate2(letexpr(ZLets,ZExpr), Result) :- %let_expression(Bids,BAssignments,BExpr)) :-
!, translate_lets(ZLets,Bids,BAssignments),
z_translate(ZExpr,BExpr),
create_z_let(expr,Bids,BAssignments,BExpr,[],b(Result,_,_)).
z_translate2(letpred(ZLets,ZExpr), Result) :- %let_predicate(Bids,BAssignments,BExpr)) :-
!, translate_lets(ZLets,Bids,BAssignments),
z_translate(ZExpr,BExpr),
create_z_let(pred,Bids,BAssignments,BExpr,[],b(Result,_,_)).
z_translate2(if(ZPred,ZIf,ZElse), if_then_else(BPred,BIf,BElse)) :-
!, z_translate(ZPred,BPred),
z_translate(ZIf,BIf), z_translate(ZElse,BElse).
z_translate2(inrel(Name,Za,Zb), member(Couple,Relation)) :-
!,z_translate(Za,Ba),z_translate(Zb,Bb),
z_translate_identifier(Name,Id),
get_texpr_type(Ba,TypeA), get_texpr_type(Bb,TypeB),
create_texpr(couple(Ba,Bb),couple(TypeA,TypeB),[],Couple),
create_texpr(identifier(Id),set(couple(TypeA,TypeB)),[],Relation).
z_translate2(binding(Bindings), rec(Fields)) :-
!, create_fields_for_binding(Bindings,Fields).
z_translate2(ftconstant(Freetype,Case),value(freeval(FreetypeId,ConstId,term(ConstId)))) :-
!,z_translate_identifier(Freetype,FreetypeId),
z_translate_identifier(Case,ConstId).
z_translate2(ftconstructor(Freetype,Case,ZExpr),
freetype_constructor(FreetypeId,CaseId,BExpr)) :-
!,z_translate(ZExpr,BExpr),
z_translate_identifier(Freetype,FreetypeId),
z_translate_identifier(Case,CaseId).
z_translate2(ftdestructor(Freetype,Case,ZExpr),
freetype_destructor(FreetypeId,CaseId,BExpr)) :-
!,z_translate(ZExpr,BExpr),
z_translate_identifier(Freetype,FreetypeId),
z_translate_identifier(Case,CaseId).
z_translate2(ftcase(Freetype,Case,ZExpr),
freetype_case(FreetypeId,CaseId,BExpr)) :-
!,z_translate(ZExpr,BExpr),
z_translate_identifier(Freetype,FreetypeId),
z_translate_identifier(Case,CaseId).
z_translate2(basetype(set(Type)), Expr) :-
!,translate_basetype2(Type,Expr).
z_translate2(reclet(ZId,ZSet), recursive_let(BId,BSet) ) :-
!,z_translate(ZId,BId),
% TODO: recursive_let accepts only comprehension sets as argument,
% maybe this should be checked here (lambda should be ok, too, because
% it's converted to a comprehension set
z_translate(ZSet,BSet1),
add_texpr_infos(BSet1,[prob_annotation('SYMBOLIC')],BSet).
z_translate2(ZBinOp, BBinOp) :-
functor(ZBinOp,ZopName,2),
is_binary_op(ZopName),!,
arg(1,ZBinOp,Za), arg(2,ZBinOp,Zb),
z_translate_binary_op(ZopName,Za,Zb,BBinOp).
z_translate2(ZUnOp, BUnOp) :-
functor(ZUnOp,ZopName,1),
is_unary_op(ZopName),!,
arg(1,ZUnOp,Zarg),
z_translate_unary_op(ZopName,Zarg,BUnOp).
z_translate2(ZExpr,_) :-
add_error(proz,'Unmatched Z expression',ZExpr),
fail.