1:- module(reif_utils,
2 [ (#<)/3
3 , (#>)/3
4 , (#=<)/3
5 , (#>=)/3
6 , (==)/3
7 , (\==)/3
8 , (@<)/3
9 , (@=<)/3
10 , (@>)/3
11 , (@>=)/3
12 , ($<)/3
13 , ($=<)/3
14 , ($>)/3
15 , ($>=)/3
16 , op(700, xfx, #>)
17 , op(700, xfx, #<)
18 , op(700, xfx, #>=)
19 , op(700, xfx, #=<)
20 , op(700, xfx, ==)
21 , op(700, xfx, \==)
22 , op(700, xfx, @<)
23 , op(700, xfx, @=<)
24 , op(700, xfx, @>)
25 , op(700, xfx, @>=)
26 , op(700, xfx, $<)
27 , op(700, xfx, $=<)
28 , op(700, xfx, $>)
29 , op(700, xfx, $>=)
30 ]). 31
32:- use_module(library(clpfd)). 33
35bool_rep(true, 1).
36bool_rep(false, 0).
37
38%! #<(+X:integer, +Y:integer, +Cond:boolean) is semidet.
39%! #<(+X:integer, +Y:integer, -Cond:boolean) is det.
40%! #<(+X:integer, -Y:integer, +Cond:boolean) is det.
41%! #<(+X:integer, -Y:integer, -Cond:boolean) is multi.
42%! #<(-X:integer, +Y:integer, +Cond:boolean) is det.
43%! #<(-X:integer, +Y:integer, -Cond:boolean) is multi.
44%! #<(-X:integer, -Y:integer, +Cond:boolean) is det.
45%! #<(-X:integer, -Y:integer, -Cond:boolean) is multi.
46%
47% True whenever 1) X is strictly less than Y and Cond is true, or 2) whenever
48% X is greater than or equal to Y and Cond is false. Intended to have zero unnecessary
49% choice points.
50#<(X, Y, Cond) :-
51 (X #< Y #<==> B), bool_rep(Cond, B).
52
53%! #>(+X:integer, +Y:integer, +Cond:boolean) is semidet.
54%! #>(+X:integer, +Y:integer, -Cond:boolean) is det.
55%! #>(+X:integer, -Y:integer, +Cond:boolean) is det.
56%! #>(+X:integer, -Y:integer, -Cond:boolean) is multi.
57%! #>(-X:integer, +Y:integer, +Cond:boolean) is det.
58%! #>(-X:integer, +Y:integer, -Cond:boolean) is multi.
59%! #>(-X:integer, -Y:integer, +Cond:boolean) is det.
60%! #>(-X:integer, -Y:integer, -Cond:boolean) is multi.
61%
62% True whenever 1) X is strictly greater than Y and Cond is true, or 2) whenever
63% X is less than or equal to Y and Cond is false. Intended to have zero unnecessary
64% choice points.
65#>(X, Y, Cond) :-
66 (X #> Y #<==> B), bool_rep(Cond, B).
67
68%! #=<(+X:integer, +Y:integer, +Cond:boolean) is semidet.
69%! #=<(+X:integer, +Y:integer, -Cond:boolean) is det.
70%! #=<(+X:integer, -Y:integer, +Cond:boolean) is det.
71%! #=<(+X:integer, -Y:integer, -Cond:boolean) is multi.
72%! #=<(-X:integer, +Y:integer, +Cond:boolean) is det.
73%! #=<(-X:integer, +Y:integer, -Cond:boolean) is multi.
74%! #=<(-X:integer, -Y:integer, +Cond:boolean) is det.
75%! #=<(-X:integer, -Y:integer, -Cond:boolean) is multi.
76%
77% True whenever 1) X is less than or equal to Y and Cond is true, or 2) whenever
78% X is strictly greater than Y and Cond is false. Intended to have zero unnecessary
79% choice points.
80#=<(X, Y, Cond) :-
81 (X #=< Y #<==> B), bool_rep(Cond, B).
82
83%! #>=(+X:integer, +Y:integer, +Cond:boolean) is semidet.
84%! #>=(+X:integer, +Y:integer, -Cond:boolean) is det.
85%! #>=(+X:integer, -Y:integer, +Cond:boolean) is det.
86%! #>=(+X:integer, -Y:integer, -Cond:boolean) is multi.
87%! #>=(-X:integer, +Y:integer, +Cond:boolean) is det.
88%! #>=(-X:integer, +Y:integer, -Cond:boolean) is multi.
89%! #>=(-X:integer, -Y:integer, +Cond:boolean) is det.
90%! #>=(-X:integer, -Y:integer, -Cond:boolean) is multi.
91%
92% True whenever 1) X is greater than or equal to Y and Cond is true, or 2) whenever
93% X is strictly less than Y and Cond is false. Intended to have zero unnecessary
94% choice points.
95#>=(X, Y, Cond) :-
96 (X #>= Y #<==> B), bool_rep(Cond, B).
111==(X, Y, Cond) :-
112 ( var(Cond)
113 -> ( X == Y -> Cond = true ; Cond = false )
114 ; ground(Cond)
115 -> ( Cond = true -> X == Y ; Cond = false -> X \== Y)
116 ).
131\==(X, Y, Cond) :-
132 ( var(Cond)
133 -> ( X \== Y -> Cond = true ; Cond = false )
134 ; ground(Cond)
135 -> ( Cond = true -> X \== Y ; Cond = false -> X == Y)
136 ).
151@<(X, Y, Cond) :-
152 ( var(Cond)
153 -> ( X @< Y -> Cond = true ; Cond = false )
154 ; ground(Cond)
155 -> ( Cond = true -> X @< Y ; Cond = false -> X @>= Y )
156 ).
171@=<(X, Y, Cond) :-
172 ( var(Cond)
173 -> ( X @=< Y -> Cond = true ; Cond = false )
174 ; ground(Cond)
175 -> ( Cond = true -> X @=< Y ; Cond = false -> X @> Y )
176 ).
191@>(X, Y, Cond) :-
192 ( var(Cond)
193 -> ( X @> Y -> Cond = true ; Cond = false )
194 ; ground(Cond)
195 -> ( Cond = true -> X @> Y ; Cond = false -> X @=< Y )
196 ).
211@>=(X, Y, Cond) :-
212 ( var(Cond)
213 -> ( X @>= Y -> Cond = true ; Cond = false )
214 ; ground(Cond)
215 -> ( Cond = true -> X @>= Y ; Cond = false -> X @< Y )
216 ).
232$<(X, Y, Cond) :-
233 ( var(Cond)
234 -> when(?=(X, Y), ( X @< Y -> Cond = true ; Cond = false ) )
235 ; ground(Cond)
236 -> ( Cond = true -> when(?=(X, Y), X @< Y) ; Cond = false -> when(?=(X, Y), X @>= Y) )
237 ).
253$=<(X, Y, Cond) :-
254 ( var(Cond)
255 -> when(?=(X, Y), ( X @=< Y -> Cond = true ; Cond = false ) )
256 ; ground(Cond)
257 -> ( Cond = true -> when(?=(X, Y), X @=< Y) ; Cond = false -> when(?=(X, Y), X @> Y) )
258 ).
274$>(X, Y, Cond) :-
275 ( var(Cond)
276 -> when(?=(X, Y), ( X @> Y -> Cond = true ; Cond = false ) )
277 ; ground(Cond)
278 -> ( Cond = true -> when(?=(X, Y), X @> Y) ; Cond = false -> when(?=(X, Y), X @=< Y) )
279 ).
295$>=(X, Y, Cond) :-
296 ( var(Cond)
297 -> when(?=(X, Y), ( X @>= Y -> Cond = true ; Cond = false ) )
298 ; ground(Cond)
299 -> ( Cond = true -> when(?=(X, Y), X @>= Y) ; Cond = false -> when(?=(X, Y), X @< Y) )
300 )