missing file
[chr.git] / builtins.pl
blob52c497acf0cbf9e7c7af77feb59c53c4cfc417fa
1 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2 % Author: Tom Schrijvers
3 % Email: Tom.Schrijvers@cs.kuleuven.be
4 % Copyright: K.U.Leuven 2004
5 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
6 :- module(builtins,
8 negate_b/2,
9 entails_b/2,
10 binds_b/2
11 ]).
13 :- use_module(hprolog).
14 :- use_module(library(lists),[append/3]).
16 %% SICStus begin
17 %% :- use_module(library(terms),[term_variables/2]).
18 %% SICStus end
20 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
21 negate_b(A,B) :- once(negate(A,B)).
22 negate((A,B),NotB) :- A==true,negate(B,NotB). % added by jon
23 negate((A,B),NotA) :- B==true,negate(A,NotA). % added by jon
24 negate((A,B),(NotA;NotB)) :- negate(A,NotA),negate(B,NotB). % added by jon
25 negate((A;B),(NotA,NotB)) :- negate(A,NotA),negate(B,NotB). % added by jon
26 negate(true,fail).
27 negate(fail,true).
28 negate(X =< Y, Y < X).
29 negate(X > Y, Y >= X).
30 negate(X >= Y, Y > X).
31 negate(X < Y, Y =< X).
32 negate(X == Y, X \== Y). % added by jon
33 negate(X \== Y, X == Y). % added by jon
34 negate(X =:= Y, X =\= Y). % added by jon
35 negate(X is Y, X =\= Y). % added by jon
36 negate(X =\= Y, X =:= Y). % added by jon
37 negate(X = Y, X \= Y). % added by jon
38 negate(X \= Y, X = Y). % added by jon
39 negate(var(X),nonvar(X)).
40 negate(nonvar(X),var(X)).
41 negate(\+ X,X). % added by jon
42 negate(X,\+ X). % added by jon
44 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
45 entails_b(fail,_) :-!.
46 entails_b(A,B) :-
47 ( var(B) ->
48 entails(A,B,[A])
50 once((
51 entails(A,C,[A]),
52 B == C
56 entails(A,A,_).
57 entails(A,C,History) :-
58 entails_(A,B),
59 \+ hprolog:memberchk_eq(B,History),
60 entails(B,C,[B|History]).
62 entails_(X > Y, X >= Y).
63 entails_(X > Y, Y < X).
64 entails_(X >= Y, Y =< X).
65 entails_(X =< Y, Y >= X). %added by jon
66 entails_(X < Y, Y > X).
67 entails_(X < Y, X =< Y).
68 entails_(X > Y, X \== Y).
69 entails_(X \== Y, Y \== X).
70 entails_(X == Y, Y == X).
71 entails_(X == Y, X =:= Y) :- ground(X). %added by jon
72 entails_(X == Y, X =:= Y) :- ground(Y). %added by jon
73 entails_(X \== Y, X =\= Y) :- ground(X). %added by jon
74 entails_(X \== Y, X =\= Y) :- ground(Y). %added by jon
75 entails_(X =:= Y, Y =:= X). %added by jon
76 entails_(X =\= Y, Y =\= X). %added by jon
77 entails_(X == Y, X >= Y). %added by jon
78 entails_(X == Y, X =< Y). %added by jon
79 entails_(ground(X),nonvar(X)).
80 entails_(compound(X),nonvar(X)).
81 entails_(atomic(X),nonvar(X)).
82 entails_(number(X),nonvar(X)).
83 entails_(atom(X),nonvar(X)).
84 entails_(fail,true).
86 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
87 binds_b(G,Vars) :-
88 binds_(G,L,[]),
89 sort(L,Vars).
91 binds_(var(_),L,L).
92 binds_(nonvar(_),L,L).
93 binds_(ground(_),L,L).
94 binds_(compound(_),L,L).
95 binds_(number(_),L,L).
96 binds_(atom(_),L,L).
97 binds_(atomic(_),L,L).
98 binds_(integer(_),L,L).
99 binds_(float(_),L,L).
101 binds_(_ > _ ,L,L).
102 binds_(_ < _ ,L,L).
103 binds_(_ =< _,L,L).
104 binds_(_ >= _,L,L).
105 binds_(_ =:= _,L,L).
106 binds_(_ =\= _,L,L).
107 binds_(_ == _,L,L).
108 binds_(_ \== _,L,L).
109 binds_(true,L,L).
111 binds_(X is _,[X|L],L).
112 binds_((G1,G2),L,T) :-
113 binds_(G1,L,R),
114 binds_(G2,R,T).
115 binds_((G1;G2),L,T) :-
116 binds_(G1,L,R),
117 binds_(G2,R,T).
118 binds_((G1->G2),L,T) :-
119 binds_(G1,L,R),
120 binds_(G2,R,T).
122 binds_(\+ G,L,T) :-
123 binds_(G,L,T).
125 binds_(G,L,T) :- term_variables(G,GVars),append(GVars,T,L). %jon