27
28:- module(scasp_common,
29 [ predicate/3,
30 c_rule/3,
31 rule/4,
32 negate_functor/2,
33 is_dual/1,
34 is_global_constraint/2, 35 split_functor/3, 36 join_functor/3, 37 create_unique_functor/3,
38 operator/3,
39 raise_negation/2, 40 intern_negation/2 41 ]).
52:- use_module(program, [has_prefix/2]).
63predicate(Predicate, Name, Args) :-
64 Predicate =.. [Name | Args],
65 \+ operator(Name, _, _),
66 Name \= not,
67 !.
80c_rule(-(H, B), H, B).
92rule(-(-(H, I), B), H, I, B).
102negate_functor(F, N) :-
103 atom_concat(n_, N0, F),
104 !,
105 N = N0.
106negate_functor(F, N) :-
107 atom_concat(n_, F, N).
116is_dual(X) :-
117 has_prefix(X, n).
123is_global_constraint(Term, Nth) :-
124 functor(Term, Name, _),
125 atom_concat(o_, Func, Name),
126 split_functor(Func, Pr, Nth),
127 Nth \== -1,
128 Pr == chk.
140split_functor(P, Name, Arity) :-
141 sub_atom(P, Plen, _, Slen, '_'),
142 sub_string(P, _, Slen, 0, NS),
143 \+ sub_string(NS, _, _, _, "_"),
144 number_string(Arity, NS),
145 !,
146 sub_atom(P, 0, Plen, _, Name).
147split_functor(P, P, -1).
151join_functor(Functor, Name, Arity) :-
152 atomic_list_concat([Name, '_', Arity], Functor).
166create_unique_functor(Hi, C, Ho) :-
167 split_functor(Hi, F, A), 168 atomic_list_concat([F, '_', C, '_', A], Ho).
172raise_negation(WrappedTerm, UserTerm),
173 nonvar(WrappedTerm), scasp_wrapper(WrappedTerm) =>
174 WrappedTerm =.. [F,ArgIn],
175 raise_negation(ArgIn, Arg),
176 UserTerm =.. [F,Arg].
177raise_negation(TermIn, UserTerm),
178 functor(TermIn, Name, _),
179 negation_name(Name, Plain)
180 =>
181 TermIn =.. [Name|Args],
182 Term =.. [Plain|Args],
183 UserTerm = -Term.
184raise_negation(Term, UserTerm) =>
185 UserTerm = Term.
186
187negation_name(Name, Plain) :-
188 atom_concat(-, Plain, Name),
189 !.
190negation_name(Name, Plain) :-
191 atom_concat('o_-', Base, Name),
192 atom_concat('o_', Base, Plain).
193
194scasp_wrapper(not(_)).
195scasp_wrapper(proved(_)).
196scasp_wrapper(chs(_)).
197scasp_wrapper(assume(_)).
202intern_negation(not(Q0), Q) =>
203 intern_negation(Q0, Q1),
204 Q = not(Q1).
205intern_negation(-Q0, Q) =>
206 Q0 =.. [Name|Args],
207 atom_concat(-, Name, NName),
208 Name \== '',
209 Q =.. [NName|Args].
210intern_negation(Q0, Q) =>
211 Q = Q0.
223operator(',', xfy, 1000).
224operator(=, xfx, 700).
225operator(\=, xfx, 700).
226operator(@<, xfx, 700).
227operator(@>, xfx, 700).
228operator(@>=, xfx, 700).
229operator(@=<, xfx, 700).
231operator(is, xfx, 700).
232operator(=:=, xfx, 700).
233operator(=\=, xfx, 700).
234operator(<, xfx, 700).
235operator(=<, xfx, 700).
236operator(>, xfx, 700).
237operator(>=, xfx, 700).
238operator(+, yfx, 500).
239operator(-, yfx, 500).
240operator(*, yfx, 400).
241operator(/, yfx, 400).
242operator(//, yfx, 400).
243operator(rem, yfx, 400).
244operator(mod, yfx, 400).
245operator(<<, yfx, 400).
246operator(>>, yfx, 400).
247operator('**', xfx, 200).
248operator(^, xfy, 200).
250operator(#=, xfx, 700).
251operator(#<>, xfx, 700).
252operator(#<, xfx, 700).
253operator(#>, xfx, 700).
254operator(#>=, xfx, 700).
255operator(#=<, xfx, 700).
257operator(::, xfx, 950)
Common predicates used in multiple files
Common and utility predicates that may be called from multiple locations.