1/*  Part of CHR (Constraint Handling Rules)
2
3    Author:        Tom Schrijvers
4    E-mail:        Tom.Schrijvers@cs.kuleuven.be
5    WWW:           http://www.swi-prolog.org
6    Copyright (c)  2004-2016, K.U. Leuven
7    All rights reserved.
8
9    Redistribution and use in source and binary forms, with or without
10    modification, are permitted provided that the following conditions
11    are met:
12
13    1. Redistributions of source code must retain the above copyright
14       notice, this list of conditions and the following disclaimer.
15
16    2. Redistributions in binary form must reproduce the above copyright
17       notice, this list of conditions and the following disclaimer in
18       the documentation and/or other materials provided with the
19       distribution.
20
21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
32    POSSIBILITY OF SUCH DAMAGE.
33*/
34
35:- module(builtins,
36	[
37		negate_b/2,
38		entails_b/2,
39		binds_b/2,
40		builtin_binds_b/2
41	]).
42:- use_module(library(dialect/hprolog)).
43:- use_module(library(lists)).
44
45%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
46negate_b(A,B) :- once(negate(A,B)).
47negate((A,B),NotB) :- A==true,negate(B,NotB). % added by jon
48negate((A,B),NotA) :- B==true,negate(A,NotA). % added by jon
49negate((A,B),(NotA;NotB)) :- negate(A,NotA),negate(B,NotB). % added by jon
50negate((A;B),(NotA,NotB)) :- negate(A,NotA),negate(B,NotB). % added by jon
51negate(true,fail).
52negate(fail,true).
53negate(X =< Y, Y < X).
54negate(X > Y, Y >= X).
55negate(X >= Y, Y > X).
56negate(X < Y, Y =< X).
57negate(X == Y, X \== Y). % added by jon
58negate(X \== Y, X == Y). % added by jon
59negate(X =:= Y, X =\= Y). % added by jon
60negate(X is Y, X =\= Y). % added by jon
61negate(X =\= Y, X =:= Y). % added by jon
62negate(X = Y, X \= Y). % added by jon
63negate(X \= Y, X = Y). % added by jon
64negate(var(X),nonvar(X)).
65negate(nonvar(X),var(X)).
66negate(\+ X,X). % added by jon
67negate(X,\+ X). % added by jon
68
69%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
70entails_b(fail,_) :-!.
71entails_b(A,B) :-
72	( var(B) ->
73		entails(A,B,[A])
74	;
75		once((
76			entails(A,C,[A]),
77			B == C
78		))
79	).
80
81entails(A,A,_).
82entails(A,C,History) :-
83	entails_(A,B),
84	\+ memberchk_eq(B,History),
85	entails(B,C,[B|History]).
86
87entails_(X > Y, X >= Y).
88entails_(X > Y, Y < X).
89entails_(X >= Y, Y =< X).
90entails_(X =< Y, Y >= X). %added by jon
91entails_(X < Y, Y > X).
92entails_(X < Y, X =< Y).
93entails_(X > Y, X \== Y).
94entails_(X \== Y, Y \== X).
95entails_(X == Y, Y == X).
96entails_(X == Y, X =:= Y) :- ground(X). %added by jon
97entails_(X == Y, X =:= Y) :- ground(Y). %added by jon
98entails_(X \== Y, X =\= Y) :- ground(X). %added by jon
99entails_(X \== Y, X =\= Y) :- ground(Y). %added by jon
100entails_(X =:= Y, Y =:= X). %added by jon
101entails_(X =\= Y, Y =\= X). %added by jon
102entails_(X == Y, X >= Y). %added by jon
103entails_(X == Y, X =< Y). %added by jon
104entails_(ground(X),nonvar(X)).
105entails_(compound(X),nonvar(X)).
106entails_(atomic(X),nonvar(X)).
107entails_(number(X),nonvar(X)).
108entails_(atom(X),nonvar(X)).
109entails_(fail,true).
110
111builtin_binds_b(G,Vars) :-
112	builtin_binds_(G,L,[]),
113	sort(L,Vars).
114
115builtin_binds_(var(_),L,L).
116builtin_binds_(nonvar(_),L,L).
117builtin_binds_(ground(_),L,L).
118builtin_binds_(compound(_),L,L).
119builtin_binds_(number(_),L,L).
120builtin_binds_(atom(_),L,L).
121builtin_binds_(atomic(_),L,L).
122builtin_binds_(integer(_),L,L).
123builtin_binds_(float(_),L,L).
124
125builtin_binds_(?=(_, _), L, L).
126builtin_binds_(_<_, L, L).
127builtin_binds_(_=:=_, L, L).
128builtin_binds_(_=<_, L, L).
129builtin_binds_(_==_, L, L).
130builtin_binds_(_=@=_, L, L).
131builtin_binds_(_=\=_, L, L).
132builtin_binds_(_>=_, L, L).
133builtin_binds_(_>_, L, L).
134builtin_binds_(_@<_, L, L).
135builtin_binds_(_@=<_, L, L).
136builtin_binds_(_@>=_, L, L).
137builtin_binds_(_@>_, L, L).
138builtin_binds_(_\==_, L, L).
139builtin_binds_(_\=@=_, L, L).
140builtin_binds_(true,L,L).
141
142% TODO: check all these SWI-Prolog built-ins for binding behavior.
143%
144% builtin_binds_(format(_,_),L,L).
145% builtin_binds_(portray(_), L, L).
146% builtin_binds_(write(_), L, L).
147% builtin_binds_(write(_),L,L).
148% builtin_binds_(write(_, _), L, L).
149% builtin_binds_(write_canonical(_), L, L).
150% builtin_binds_(write_canonical(_, _), L, L).
151% builtin_binds_(write_term(_, _), L, L).
152% builtin_binds_(write_term(_, _, _), L, L).
153% builtin_binds_(writef(_), L, L).
154% builtin_binds_(writef(_, _), L, L).
155% builtin_binds_(writeln(_), L, L).
156% builtin_binds_(writeln(_),L,L).
157% builtin_binds_(writeq(_), L, L).
158% builtin_binds_(writeq(_, _), L, L).
159%
160% builtin_binds_(!(_), L, L).
161% builtin_binds_(!, L, L).
162% builtin_binds_((_'|'_), L, L).
163% builtin_binds_((_*->_), L, L).
164% builtin_binds_(abolish(_), L, L).
165% builtin_binds_(abolish(_, _), L, L).
166% builtin_binds_(abort, L, L).
167% builtin_binds_(absolute_file_name(_, _), L, L).
168% builtin_binds_(absolute_file_name(_, _, _), L, L).
169% builtin_binds_(access_file(_, _), L, L).
170% builtin_binds_(acyclic_term(_), L, L).
171% builtin_binds_(add_import_module(_, _, _), L, L).
172% builtin_binds_(append(_), L, L).
173% builtin_binds_(apply(_, _), L, L).
174% builtin_binds_(arg(_, _, _), L, L).
175% builtin_binds_(arithmetic_function(_), L, L).
176% builtin_binds_(assert(_), L, L).
177% builtin_binds_(assert(_, _), L, L).
178% builtin_binds_(asserta(_), L, L).
179% builtin_binds_(asserta(_, _), L, L).
180% builtin_binds_(assertz(_), L, L).
181% builtin_binds_(assertz(_, _), L, L).
182% builtin_binds_(at_end_of_stream(_), L, L).
183% builtin_binds_(at_end_of_stream, L, L).
184% builtin_binds_(at_halt(_), L, L).
185% builtin_binds_(at_initialization(_), L, L).
186% builtin_binds_(atom(_), L, L).
187% builtin_binds_(atom_chars(_, _), L, L).
188% builtin_binds_(atom_codes(_, _), L, L).
189% builtin_binds_(atom_concat(_, _, _), L, L).
190% builtin_binds_(atom_length(_, _), L, L).
191% builtin_binds_(atom_number(_, _), L, L).
192% builtin_binds_(atom_prefix(_, _), L, L).
193% builtin_binds_(atom_to_term(_, _, _), L, L).
194% builtin_binds_(atomic(_), L, L).
195% builtin_binds_(attvar(_), L, L).
196% builtin_binds_(autoload(_), L, L).
197% builtin_binds_(autoload, L, L).
198% builtin_binds_(b_getval(_, _), L, L).
199% builtin_binds_(b_setval(_, _), L, L).
200% builtin_binds_(bagof(_, _, _), L, L).
201% builtin_binds_(between(_, _, _), L, L).
202% builtin_binds_(block(_, _, _), L, L).
203% builtin_binds_(break, L, L).
204% builtin_binds_(byte_count(_, _), L, L).
205% builtin_binds_(call(_), L, L).
206% builtin_binds_(call(_, _), L, L).
207% builtin_binds_(call(_, _, _), L, L).
208% builtin_binds_(call(_, _, _, _), L, L).
209% builtin_binds_(call(_, _, _, _, _), L, L).
210% builtin_binds_(call(_, _, _, _, _, _), L, L).
211% builtin_binds_(call(_, _, _, _, _, _, _), L, L).
212% builtin_binds_(call(_, _, _, _, _, _, _, _), L, L).
213% builtin_binds_(call(_, _, _, _, _, _, _, _, _), L, L).
214% builtin_binds_(call(_, _, _, _, _, _, _, _, _, _), L, L).
215% builtin_binds_(call(_, _, _, _, _, _, _, _, _, _, _), L, L).
216% builtin_binds_(call_cleanup(_, _), L, L).
217% builtin_binds_(call_cleanup(_, _, _), L, L).
218% builtin_binds_(call_shared_object_function(_, _), L, L).
219% builtin_binds_(call_with_depth_limit(_, _, _), L, L).
220% builtin_binds_(callable(_), L, L).
221% builtin_binds_(catch(_, _, _), L, L).
222% builtin_binds_(char_code(_, _), L, L).
223% builtin_binds_(char_conversion(_, _), L, L).
224% builtin_binds_(char_type(_, _), L, L).
225% builtin_binds_(character_count(_, _), L, L).
226% builtin_binds_(clause(_, _), L, L).
227% builtin_binds_(clause(_, _, _), L, L).
228% builtin_binds_(clause_property(_, _), L, L).
229% builtin_binds_(close(_), L, L).
230% builtin_binds_(close(_, _), L, L).
231% builtin_binds_(close_shared_object(_), L, L).
232% builtin_binds_(code_type(_, _), L, L).
233% builtin_binds_(collation_key(_, _), L, L).
234% builtin_binds_(compare(_, _, _), L, L).
235% builtin_binds_(compile_aux_clauses(_), L, L).
236% builtin_binds_(compile_predicates(_), L, L).
237% builtin_binds_(compiling, L, L).
238% builtin_binds_(compound(_), L, L).
239% builtin_binds_(concat_atom(_, _), L, L).
240% builtin_binds_(concat_atom(_, _, _), L, L).
241% builtin_binds_(consult(_), L, L).
242% builtin_binds_(context_module(_), L, L).
243% builtin_binds_(copy_stream_data(_, _), L, L).
244% builtin_binds_(copy_stream_data(_, _, _), L, L).
245% builtin_binds_(copy_term(_, _), L, L).
246% builtin_binds_(copy_term_nat(_, _), L, L).
247% builtin_binds_(current_arithmetic_function(_), L, L).
248% builtin_binds_(current_atom(_), L, L).
249% builtin_binds_(current_blob(_, _), L, L).
250% builtin_binds_(current_char_conversion(_, _), L, L).
251% builtin_binds_(current_flag(_), L, L).
252% builtin_binds_(current_format_predicate(_, _), L, L).
253% builtin_binds_(current_functor(_, _), L, L).
254% builtin_binds_(current_input(_), L, L).
255% builtin_binds_(current_key(_), L, L).
256% builtin_binds_(current_module(_), L, L).
257% builtin_binds_(current_module(_, _), L, L).
258% builtin_binds_(current_op(_, _, _), L, L).
259% builtin_binds_(current_output(_), L, L).
260% builtin_binds_(current_predicate(_), L, L).
261% builtin_binds_(current_predicate(_, _), L, L).
262% builtin_binds_(current_prolog_flag(_, _), L, L).
263% builtin_binds_(current_resource(_, _, _), L, L).
264% builtin_binds_(current_signal(_, _, _), L, L).
265% builtin_binds_(cyclic_term(_), L, L).
266% builtin_binds_(date_time_stamp(_, _), L, L).
267% builtin_binds_(debugging, L, L).
268% builtin_binds_(default_module(_, _), L, L).
269% builtin_binds_(del_attr(_, _), L, L).
270% builtin_binds_(delete_directory(_), L, L).
271% builtin_binds_(delete_file(_), L, L).
272% builtin_binds_(delete_import_module(_, _), L, L).
273% builtin_binds_(deterministic(_), L, L).
274% builtin_binds_(downcase_atom(_, _), L, L).
275% builtin_binds_(duplicate_term(_, _), L, L).
276% builtin_binds_(dwim_match(_, _), L, L).
277% builtin_binds_(dwim_match(_, _, _), L, L).
278% builtin_binds_(dwim_predicate(_, _), L, L).
279% builtin_binds_(ensure_loaded(_), L, L).
280% builtin_binds_(erase(_), L, L).
281% builtin_binds_(eval_license, L, L).
282% builtin_binds_(exists_directory(_), L, L).
283% builtin_binds_(exists_file(_), L, L).
284% builtin_binds_(exit(_, _), L, L).
285% builtin_binds_(expand_file_name(_, _), L, L).
286% builtin_binds_(expand_file_search_path(_, _), L, L).
287% builtin_binds_(expand_goal(_, _), L, L).
288% builtin_binds_(expand_term(_, _), L, L).
289% builtin_binds_(export(_), L, L).
290% builtin_binds_(export_list(_, _), L, L).
291% builtin_binds_(fail(_), L, L).
292% builtin_binds_(fail, L, L).
293% builtin_binds_(file_base_name(_, _), L, L).
294% builtin_binds_(file_directory_name(_, _), L, L).
295% builtin_binds_(file_name_extension(_, _, _), L, L).
296% builtin_binds_(fileerrors(_, _), L, L).
297% builtin_binds_(findall(_, _, _), L, L).
298% builtin_binds_(findall(_, _, _, _), L, L).
299% builtin_binds_(flag(_, _, _), L, L).
300% builtin_binds_(float(_), L, L).
301% builtin_binds_(flush_output(_), L, L).
302% builtin_binds_(flush_output, L, L).
303% builtin_binds_(forall(_, _), L, L).
304% builtin_binds_(format(_), L, L).
305% builtin_binds_(format(_, _), L, L).
306% builtin_binds_(format(_, _, _), L, L).
307% builtin_binds_(format_predicate(_, _), L, L).
308% builtin_binds_(format_time(_, _, _), L, L).
309% builtin_binds_(format_time(_, _, _, _), L, L).
310% builtin_binds_(freeze(_, _), L, L).
311% builtin_binds_(frozen(_, _), L, L).
312% builtin_binds_(functor(_, _, _), L, L).
313% builtin_binds_(garbage_collect, L, L).
314% builtin_binds_(garbage_collect_atoms, L, L).
315% builtin_binds_(garbage_collect_clauses, L, L).
316% builtin_binds_(get(_), L, L).
317% builtin_binds_(get(_, _), L, L).
318% builtin_binds_(get0(_), L, L).
319% builtin_binds_(get0(_, _), L, L).
320% builtin_binds_(get_attr(_, _, _), L, L).
321% builtin_binds_(get_attrs(_, _), L, L).
322% builtin_binds_(get_byte(_), L, L).
323% builtin_binds_(get_byte(_, _), L, L).
324% builtin_binds_(get_char(_), L, L).
325% builtin_binds_(get_char(_, _), L, L).
326% builtin_binds_(get_code(_), L, L).
327% builtin_binds_(get_code(_, _), L, L).
328% builtin_binds_(get_single_char(_), L, L).
329% builtin_binds_(get_time(_), L, L).
330% builtin_binds_(getenv(_, _), L, L).
331% builtin_binds_(ground(_), L, L).
332% builtin_binds_(halt(_), L, L).
333% builtin_binds_(halt, L, L).
334% builtin_binds_(hash(_), L, L).
335% builtin_binds_(term_hash(_, _), L, L).
336% builtin_binds_(ignore(_), L, L).
337% builtin_binds_(import(_), L, L).
338% builtin_binds_(import_module(_, _), L, L).
339% builtin_binds_(index(_), L, L).
340% builtin_binds_(integer(_), L, L).
341% builtin_binds_(is_absolute_file_name(_), L, L).
342% builtin_binds_(is_list(_), L, L).
343% builtin_binds_(is_stream(_), L, L).
344% builtin_binds_(keysort(_, _), L, L).
345% builtin_binds_(leash(_), L, L).
346% builtin_binds_(length(_, _), L, L).
347% builtin_binds_(license(_), L, L).
348% builtin_binds_(license(_, _), L, L).
349% builtin_binds_(line_count(_, _), L, L).
350% builtin_binds_(line_position(_, _), L, L).
351% builtin_binds_(load_files(_), L, L).
352% builtin_binds_(load_files(_, _), L, L).
353% builtin_binds_(make_directory(_), L, L).
354% builtin_binds_(make_library_index(_), L, L).
355% builtin_binds_(make_library_index(_, _), L, L).
356% builtin_binds_(maplist(_, _), L, L).
357% builtin_binds_(maplist(_, _, _), L, L).
358% builtin_binds_(maplist(_, _, _, _), L, L).
359% builtin_binds_(memberchk(_, _), L, L).
360% builtin_binds_(message_queue_create(_), L, L).
361% builtin_binds_(message_queue_create(_, _), L, L).
362% builtin_binds_(message_queue_destroy(_), L, L).
363% builtin_binds_(message_queue_property(_, _), L, L).
364% builtin_binds_(message_to_string(_, _), L, L).
365% builtin_binds_(module(_), L, L).
366% builtin_binds_(msort(_, _), L, L).
367% builtin_binds_(mutex_create(_), L, L).
368% builtin_binds_(mutex_create(_, _), L, L).
369% builtin_binds_(mutex_destroy(_), L, L).
370% builtin_binds_(mutex_lock(_), L, L).
371% builtin_binds_(mutex_property(_, _), L, L).
372% builtin_binds_(mutex_statistics, L, L).
373% builtin_binds_(mutex_trylock(_), L, L).
374% builtin_binds_(mutex_unlock(_), L, L).
375% builtin_binds_(mutex_unlock_all, L, L).
376% builtin_binds_(name(_, _), L, L).
377% builtin_binds_(nb_current(_, _), L, L).
378% builtin_binds_(nb_delete(_), L, L).
379% builtin_binds_(nb_getval(_, _), L, L).
380% builtin_binds_(nb_linkarg(_, _, _), L, L).
381% builtin_binds_(nb_linkval(_, _), L, L).
382% builtin_binds_(nb_setarg(_, _, _), L, L).
383% builtin_binds_(nb_setval(_, _), L, L).
384% builtin_binds_(nl(_), L, L).
385% builtin_binds_(nl, L, L).
386% builtin_binds_(nonvar(_), L, L).
387% builtin_binds_(noprofile(_), L, L).
388% builtin_binds_(noprotocol, L, L).
389% builtin_binds_(nospy(_), L, L).
390% builtin_binds_(nospyall, L, L).
391% builtin_binds_(not(_), L, L).
392% builtin_binds_(notrace(_), L, L).
393% builtin_binds_(notrace, L, L).
394% builtin_binds_(nth_clause(_, _, _), L, L).
395% builtin_binds_(number(_), L, L).
396% builtin_binds_(number_chars(_, _), L, L).
397% builtin_binds_(number_codes(_, _), L, L).
398% builtin_binds_(numbervars(_, _, _), L, L).
399% builtin_binds_(numbervars(_, _, _, _), L, L).
400% builtin_binds_(on_signal(_, _, _), L, L).
401% builtin_binds_(once(_), L, L).
402% builtin_binds_(op(_, _, _), L, L).
403% builtin_binds_(open(_, _, _), L, L).
404% builtin_binds_(open(_, _, _, _), L, L).
405% builtin_binds_(open_null_stream(_), L, L).
406% builtin_binds_(open_resource(_, _, _), L, L).
407% builtin_binds_(open_resource(_, _, _, _), L, L).
408% builtin_binds_(open_shared_object(_, _), L, L).
409% builtin_binds_(open_shared_object(_, _, _), L, L).
410% builtin_binds_(open_xterm(_, _, _, _), L, L).
411% builtin_binds_(peek_byte(_), L, L).
412% builtin_binds_(peek_byte(_, _), L, L).
413% builtin_binds_(peek_char(_), L, L).
414% builtin_binds_(peek_char(_, _), L, L).
415% builtin_binds_(peek_code(_), L, L).
416% builtin_binds_(peek_code(_, _), L, L).
417% builtin_binds_(phrase(_, _), L, L).
418% builtin_binds_(phrase(_, _, _), L, L).
419% builtin_binds_(plus(_, _, _), L, L).
420% builtin_binds_(predicate_property(_, _), L, L).
421% builtin_binds_(preprocessor(_, _), L, L).
422% builtin_binds_(print(_), L, L).
423% builtin_binds_(print(_, _), L, L).
424% builtin_binds_(print_message(_, _), L, L).
425% builtin_binds_(print_message_lines(_, _, _), L, L).
426% builtin_binds_(profiler(_, _), L, L).
427% builtin_binds_(prolog, L, L).
428% builtin_binds_(prolog_choice_attribute(_, _, _), L, L).
429% builtin_binds_(prolog_current_frame(_), L, L).
430% builtin_binds_(prolog_frame_attribute(_, _, _), L, L).
431% builtin_binds_(prolog_load_context(_, _), L, L).
432% builtin_binds_(prolog_skip_level(_, _), L, L).
433% builtin_binds_(prolog_to_os_filename(_, _), L, L).
434% builtin_binds_(prompt(_, _), L, L).
435% builtin_binds_(prompt1(_), L, L).
436% builtin_binds_(protocol(_), L, L).
437% builtin_binds_(protocola(_), L, L).
438% builtin_binds_(protocolling(_), L, L).
439% builtin_binds_(put(_), L, L).
440% builtin_binds_(put(_, _), L, L).
441% builtin_binds_(put_attr(_, _, _), L, L).
442% builtin_binds_(put_attrs(_, _), L, L).
443% builtin_binds_(put_byte(_), L, L).
444% builtin_binds_(put_byte(_, _), L, L).
445% builtin_binds_(put_char(_), L, L).
446% builtin_binds_(put_char(_, _), L, L).
447% builtin_binds_(put_code(_), L, L).
448% builtin_binds_(put_code(_, _), L, L).
449% builtin_binds_(qcompile(_), L, L).
450% builtin_binds_(rational(_), L, L).
451% builtin_binds_(rational(_, _, _), L, L).
452% builtin_binds_(read(_), L, L).
453% builtin_binds_(read(_, _), L, L).
454% builtin_binds_(read_clause(_), L, L).
455% builtin_binds_(read_clause(_, _), L, L).
456% builtin_binds_(read_history(_, _, _, _, _, _), L, L).
457% builtin_binds_(read_link(_, _, _), L, L).
458% builtin_binds_(read_pending_codes(_, _, _), L, L).
459% builtin_binds_(read_pending_chars(_, _, _), L, L).
460% builtin_binds_(read_term(_, _), L, L).
461% builtin_binds_(read_term(_, _, _), L, L).
462% builtin_binds_(recorda(_, _), L, L).
463% builtin_binds_(recorda(_, _, _), L, L).
464% builtin_binds_(recorded(_, _), L, L).
465% builtin_binds_(recorded(_, _, _), L, L).
466% builtin_binds_(recordz(_, _), L, L).
467% builtin_binds_(recordz(_, _, _), L, L).
468% builtin_binds_(redefine_system_predicate(_), L, L).
469% builtin_binds_(reload_library_index, L, L).
470% builtin_binds_(rename_file(_, _), L, L).
471% builtin_binds_(repeat, L, L).
472% builtin_binds_(require(_), L, L).
473% builtin_binds_(reset_profiler, L, L).
474% builtin_binds_(retract(_), L, L).
475% builtin_binds_(retractall(_), L, L).
476% builtin_binds_(same_file(_, _), L, L).
477% builtin_binds_(same_term(_, _), L, L).
478% builtin_binds_(see(_), L, L).
479% builtin_binds_(seeing(_), L, L).
480% builtin_binds_(seek(_, _, _, _), L, L).
481% builtin_binds_(seen, L, L).
482% builtin_binds_(set_input(_), L, L).
483% builtin_binds_(set_output(_), L, L).
484% builtin_binds_(set_prolog_IO(_, _, _), L, L).
485% builtin_binds_(set_prolog_flag(_, _), L, L).
486% builtin_binds_(set_stream(_, _), L, L).
487% builtin_binds_(set_stream_position(_, _), L, L).
488% builtin_binds_(setarg(_, _, _), L, L).
489% builtin_binds_(setenv(_, _), L, L).
490% builtin_binds_(setlocale(_, _, _), L, L).
491% builtin_binds_(setof(_, _, _), L, L).
492% builtin_binds_(setup_and_call_cleanup(_, _, _), L, L).
493% builtin_binds_(setup_and_call_cleanup(_, _, _, _), L, L).
494% builtin_binds_(shell(_), L, L).
495% builtin_binds_(shell(_, _), L, L).
496% builtin_binds_(shell, L, L).
497% builtin_binds_(size_file(_, _), L, L).
498% builtin_binds_(skip(_), L, L).
499% builtin_binds_(skip(_, _), L, L).
500% builtin_binds_(sleep(_), L, L).
501% builtin_binds_(sort(_, _), L, L).
502% builtin_binds_(source_file(_), L, L).
503% builtin_binds_(source_file(_, _), L, L).
504% builtin_binds_(source_location(_, _), L, L).
505% builtin_binds_(spy(_), L, L).
506% builtin_binds_(stamp_date_time(_, _, _), L, L).
507% builtin_binds_(statistics(_, _), L, L).
508% builtin_binds_(statistics, L, L).
509% builtin_binds_(stream_position_data(_, _, _), L, L).
510% builtin_binds_(stream_property(_, _), L, L).
511% builtin_binds_(string(_), L, L).
512% builtin_binds_(string_concat(_, _, _), L, L).
513% builtin_binds_(string_length(_, _), L, L).
514% builtin_binds_(atom_string(_, _), L, L).
515% builtin_binds_(string_codes(_, _), L, L).
516% builtin_binds_(strip_module(_, _, _), L, L).
517% builtin_binds_(style_check(_), L, L).
518% builtin_binds_(sub_atom(_, _, _, _, _), L, L).
519% builtin_binds_(sub_string(_, _, _, _, _), L, L).
520% builtin_binds_(succ(_, _), L, L).
521% builtin_binds_(swritef(_, _), L, L).
522% builtin_binds_(swritef(_, _, _), L, L).
523% builtin_binds_(tab(_), L, L).
524% builtin_binds_(tab(_, _), L, L).
525% builtin_binds_(tell(_), L, L).
526% builtin_binds_(telling(_), L, L).
527% builtin_binds_(term_to_atom(_, _), L, L).
528% builtin_binds_(term_variables(_, _), L, L).
529% builtin_binds_(term_variables(_, _, _), L, L).
530% builtin_binds_(thread_at_exit(_), L, L).
531% builtin_binds_(thread_create(_, _, _), L, L).
532% builtin_binds_(thread_detach(_), L, L).
533% builtin_binds_(thread_exit(_), L, L).
534% builtin_binds_(thread_get_message(_), L, L).
535% builtin_binds_(thread_get_message(_, _), L, L).
536% builtin_binds_(thread_join(_, _), L, L).
537% builtin_binds_(thread_kill(_, _), L, L).
538% builtin_binds_(thread_peek_message(_), L, L).
539% builtin_binds_(thread_peek_message(_, _), L, L).
540% builtin_binds_(thread_property(_, _), L, L).
541% builtin_binds_(thread_self(_), L, L).
542% builtin_binds_(thread_send_message(_, _), L, L).
543% builtin_binds_(thread_setconcurrency(_, _), L, L).
544% builtin_binds_(thread_signal(_, _), L, L).
545% builtin_binds_(thread_statistics(_, _, _), L, L).
546% builtin_binds_(throw(_), L, L).
547% builtin_binds_(time_file(_, _), L, L).
548% builtin_binds_(tmp_file(_, _), L, L).
549% builtin_binds_(told, L, L).
550% builtin_binds_(trim_stacks, L, L).
551% builtin_binds_(tty_get_capability(_, _, _), L, L).
552% builtin_binds_(tty_goto(_, _), L, L).
553% builtin_binds_(tty_put(_, _), L, L).
554% builtin_binds_(tty_size(_, _), L, L).
555% builtin_binds_(ttyflush, L, L).
556% builtin_binds_(unifiable(_, _, _), L, L).
557% builtin_binds_(unify_with_occurs_check(_, _), L, L).
558% builtin_binds_(unsetenv(_), L, L).
559% builtin_binds_(upcase_atom(_, _), L, L).
560% builtin_binds_(wait_for_input(_, _, _), L, L).
561% builtin_binds_(wildcard_match(_, _), L, L).
562% builtin_binds_(with_mutex(_, _), L, L).
563% builtin_binds_(with_output_to(_, _), L, L).
564% builtin_binds_(working_directory(_, _), L, L).
565
566
567% builtin_binds_(functor(Term, Functor, Arity), [Term,Functor,Arity|T], T).
568% builtin_binds_(arg(Arg, Term, Pos), [Arg,Term,Pos|T], T).
569% builtin_binds_(term_variables(_, _), L, L).
570% builtin_binds_(X=Y, [X,Y|T], T).
571
572
573builtin_binds_(X is _,[X|L],L).
574builtin_binds_((G1,G2),L,T) :-
575	builtin_binds_(G1,L,R),
576	builtin_binds_(G2,R,T).
577builtin_binds_((G1;G2),L,T) :-
578	builtin_binds_(G1,L,R),
579	builtin_binds_(G2,R,T).
580builtin_binds_((G1->G2),L,T) :-
581	builtin_binds_(G1,L,R),
582	builtin_binds_(G2,R,T).
583
584builtin_binds_(\+ G,L,T) :-
585	builtin_binds_(G,L,T).
586%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
587binds_b(G,Vars) :-
588	binds_(G,L,[]),
589	sort(L,Vars).
590
591binds_(var(_),L,L).
592binds_(nonvar(_),L,L).
593binds_(ground(_),L,L).
594binds_(compound(_),L,L).
595binds_(number(_),L,L).
596binds_(atom(_),L,L).
597binds_(atomic(_),L,L).
598binds_(integer(_),L,L).
599binds_(float(_),L,L).
600
601binds_(_ > _ ,L,L).
602binds_(_ < _ ,L,L).
603binds_(_ =< _,L,L).
604binds_(_ >= _,L,L).
605binds_(_ =:= _,L,L).
606binds_(_ =\= _,L,L).
607binds_(_ == _,L,L).
608binds_(_ \== _,L,L).
609binds_(true,L,L).
610
611binds_(write(_),L,L).
612binds_(writeln(_),L,L).
613binds_(format(_,_),L,L).
614
615binds_(X is _,[X|L],L).
616binds_((G1,G2),L,T) :-
617	binds_(G1,L,R),
618	binds_(G2,R,T).
619binds_((G1;G2),L,T) :-
620	binds_(G1,L,R),
621	binds_(G2,R,T).
622binds_((G1->G2),L,T) :-
623	binds_(G1,L,R),
624	binds_(G2,R,T).
625
626binds_(\+ G,L,T) :-
627	binds_(G,L,T).
628
629binds_(G,L,T) :- term_variables(G,GVars),append(GVars,T,L).	%jon
630