Re-generated configure
[chr.git] / Benchmarks / fulladder.chr
blob1d20a3cdacfe6971bb60871258190909eb9e98fa
1 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2 %%
3 %% Thom Fruehwirth ECRC 1991-1993
4 %% 910528 started boolean,and,or constraints
5 %% 910904 added xor,neg constraints
6 %% 911120 added imp constraint
7 %% 931110 ported to new release
8 %% 931111 added card constraint 
9 %% 961107 Christian Holzbaur, SICStus mods
11 %% ported to hProlog by Tom Schrijvers June 2003
14 :- module(fulladder,[main/0,main/1]).
16 :- constraints and/3, or/3, xor/3, neg/2.
18 :- use_module(library(lists)).
20 %% and/3 specification
21 %%and(0,0,0).
22 %%and(0,1,0).
23 %%and(1,0,0).
24 %%and(1,1,1).
26 and(0,X,Y) <=> Y=0.
27 and(X,0,Y) <=> Y=0.
28 and(1,X,Y) <=> Y=X.
29 and(X,1,Y) <=> Y=X.
30 and(X,Y,1) <=> X=1,Y=1.
31 and(X,X,Z) <=> X=Z.
32 and(X,Y,A) \ and(X,Y,B) <=> A=B, chr_dummy.
33 and(X,Y,A) \ and(Y,X,B) <=> A=B, chr_dummy.
35 %% or/3 specification
36 %%or(0,0,0).
37 %%or(0,1,1).
38 %%or(1,0,1).
39 %%or(1,1,1).
41 or(0,X,Y) <=> Y=X.
42 or(X,0,Y) <=> Y=X.
43 or(X,Y,0) <=> X=0,Y=0.
44 or(1,X,Y) <=> Y=1.
45 or(X,1,Y) <=> Y=1.
46 or(X,X,Z) <=> X=Z.
47 or(X,Y,A) \ or(X,Y,B) <=> A=B, chr_dummy.
48 or(X,Y,A) \ or(Y,X,B) <=> A=B, chr_dummy.
50 %% xor/3 specification
51 %%xor(0,0,0).
52 %%xor(0,1,1).
53 %%xor(1,0,1).
54 %%xor(1,1,0).
56 xor(0,X,Y) <=> X=Y.
57 xor(X,0,Y) <=> X=Y.
58 xor(X,Y,0) <=> X=Y.
59 xor(1,X,Y) <=> neg(X,Y).
60 xor(X,1,Y) <=> neg(X,Y).
61 xor(X,Y,1) <=> neg(X,Y).
62 xor(X,X,Y) <=> Y=0.
63 xor(X,Y,X) <=> Y=0.
64 xor(Y,X,X) <=> Y=0.
65 xor(X,Y,A) \ xor(X,Y,B) <=> A=B, chr_dummy.
66 xor(X,Y,A) \ xor(Y,X,B) <=> A=B, chr_dummy.
68 %% neg/2 specification
69 %%neg(0,1).
70 %%neg(1,0).
72 neg(0,X) <=> X=1.
73 neg(X,0) <=> X=1.
74 neg(1,X) <=> X=0.
75 neg(X,1) <=> X=0.
76 neg(X,X) <=> fail.
77 neg(X,Y) \ neg(Y,Z) <=> X=Z, chr_dummy. 
78 neg(X,Y) \ neg(Z,Y) <=> X=Z, chr_dummy. 
79 neg(Y,X) \ neg(Y,Z) <=> X=Z, chr_dummy. 
80 %% Interaction with other boolean constraints
81 neg(X,Y) \ and(X,Y,Z) <=> Z=0, chr_dummy.
82 neg(Y,X) \ and(X,Y,Z) <=> Z=0, chr_dummy.
83 neg(X,Z) , and(X,Y,Z) <=> X=1,Y=0,Z=0.
84 neg(Z,X) , and(X,Y,Z) <=> X=1,Y=0,Z=0.
85 neg(Y,Z) , and(X,Y,Z) <=> X=0,Y=1,Z=0.
86 neg(Z,Y) , and(X,Y,Z) <=> X=0,Y=1,Z=0.
87 neg(X,Y) \ or(X,Y,Z) <=> Z=1, chr_dummy.
88 neg(Y,X) \ or(X,Y,Z) <=> Z=1, chr_dummy.
89 neg(X,Z) , or(X,Y,Z) <=> X=0,Y=1,Z=1.
90 neg(Z,X) , or(X,Y,Z) <=> X=0,Y=1,Z=1.
91 neg(Y,Z) , or(X,Y,Z) <=> X=1,Y=0,Z=1.
92 neg(Z,Y) , or(X,Y,Z) <=> X=1,Y=0,Z=1.
93 neg(X,Y) \ xor(X,Y,Z) <=> Z=1, chr_dummy.
94 neg(Y,X) \ xor(X,Y,Z) <=> Z=1, chr_dummy.
95 neg(X,Z) \ xor(X,Y,Z) <=> Y=1, chr_dummy.
96 neg(Z,X) \ xor(X,Y,Z) <=> Y=1, chr_dummy.
97 neg(Y,Z) \ xor(X,Y,Z) <=> X=1, chr_dummy.
98 neg(Z,Y) \ xor(X,Y,Z) <=> X=1, chr_dummy.
100 /* end of handler bool */
102 half_adder(X,Y,S,C) :-
103         xor(X,Y,S),
104         and(X,Y,C).
106 full_adder(X,Y,Ci,S,Co) :-
107         half_adder(X,Y,S1,Co1),
108         half_adder(Ci,S1,S,Co2),
109         or(Co1,Co2,Co).
111 main :-
112         main(6000).
114 main(N) :-
115         cputime(X),
116         adder(N),
117         cputime(Now),
118         Time is Now - X,
119         write(bench(bool ,N,Time,0,hprolog)),write('.'),nl.
121 adder(N) :-
122         length(Ys,N),
123         add(N,Ys).
125 add(N,[Y|Ys]) :-
126         half_adder(1,Y,0,C),
127         add0(Ys,C).
129 add0([],1).
130 add0([Y|Ys],C) :-
131         full_adder(0,Y,C,1,NC),
132         add1(Ys,NC).
134 add1([],0).
135 add1([Y|Ys],C) :-
136         full_adder(1,Y,C,0,NC),
137         add0(Ys,NC).