1 //          Copyright Ellery Newcomer 2011 - 2014.
2 // Distributed under the Boost Software License, Version 1.0.
3 //    (See accompanying file LICENSE_1_0.txt or copy at
4 //          http://www.boost.org/LICENSE_1_0.txt)
5 module bitall;
6 /++ 
7  + This module contains algorithms for finding the minimum and maximum of
8  + an expression a op b, where
9  + a and b range through the integer intervals [amin, amax], [bmin, bmax].
10  + op is one of the binary operators:
11  +    & | ^ 
12  +    for either signed or unsigned arithmetic
13  +
14  + There should be an accompanying pdf file which describes the derivation
15  + of the following algorithms. Refer to it.
16  +/
17 
18 import std.algorithm, std.conv, std.stdio, std.traits;
19 static import core.bitop;
20 
21 template signed(T) {
22     static if(isSigned!T) alias T signed;
23     else static if(is(T == ubyte)) alias byte signed;
24     else static if(is(T == ushort)) alias short signed;
25     else static if(is(T == uint)) alias int signed;
26     else static if(is(T == ulong)) alias long signed;
27 }
28 static assert(is( signed!(ubyte) == byte));
29 static assert(is( signed!(byte) == byte));
30 
31 template unsigned(T) {
32     static if(isUnsigned!T) alias T unsigned;
33     else static if(is(T == byte)) alias ubyte unsigned;
34     else static if(is(T == short)) alias ushort unsigned;
35     else static if(is(T == int)) alias uint unsigned;
36     else static if(is(T == long)) alias ulong unsigned;
37 }
38 
39 static assert(is( unsigned!(ubyte) == ubyte));
40 static assert(is( unsigned!(byte) == ubyte));
41 
42 private template bsr(T) if(isIntegral!T) {
43     static if(uint.sizeof < T.sizeof) {
44         static assert(T.sizeof == ulong.sizeof);
45         T bsr(T x) {
46             uint* xsp = cast(uint*) &x;
47             uint xl = xsp[0], xh = xsp[1];
48             if(xh) return core.bitop.bsr(xh) + 32;
49             else return core.bitop.bsr(xl);
50         }
51     }else static if(uint.sizeof == T.sizeof) {
52         alias core.bitop.bsr bsr;
53     }else{
54         T bsr(T x) {
55             return cast(T) core.bitop.bsr(x & (cast(unsigned!T) -1));
56         }
57     }
58 }
59 
60 unittest{
61     assert(bsr!ubyte(0x7f) == 6);
62     assert(bsr!byte(0x7f) == 6);
63     assert(bsr!ubyte(0x80) == 7);
64     assert(bsr!byte(cast(byte)0x80) == 7);
65     assert(bsr!ushort(0x7f) == 6);
66     assert(bsr!short(0x7f) == 6);
67     assert(bsr!uint(0x7f) == 6);
68     assert(bsr!int(0x7f) == 6);
69     assert(bsr!ulong(0x7f) == 6);
70     assert(bsr!long(0x7f) == 6);
71     assert(bsr!ulong(0x7f_ff) == 14);
72     assert(bsr!long(0x7f_ff) == 14);
73     assert(bsr!ulong(0x7f_ff_ff) == 22);
74     assert(bsr!long(0x7f_ff_ff) == 22);
75     assert(bsr!ulong(0x7f_ff_ff_ff) == 30);
76     assert(bsr!long(0x7f_ff_ff_ff) == 30);
77     assert(bsr!ulong(0x7f_ff_ff_ff_ff_ff_ff_ffUL) == 62);
78     assert(bsr!long(0x7f_ff_ff_ff_ff_ff_ff_ffUL) == 62);
79     assert(bsr!ulong(0x80_00_00_00_00_00_00_00UL) == 63);
80     assert(bsr!long(0x80_00_00_00_00_00_00_00UL) == 63);
81 }
82 
83 I hbmask(I)(I i) if(isIntegral!I) {
84     return cast(I) ((cast(I)1 << bsr!I(i|1))-1);
85 }
86 
87 unittest{
88     assert(hbmask(0) == 0);
89     assert(hbmask(1) == 0);
90     assert(hbmask(0b101011100011) 
91             ==    0b011111111111);
92     assert(hbmask!ubyte(0x05) == 0x03);
93     assert(hbmask!ubyte(0x40) == 0x3f);
94     assert(hbmask!ubyte(0x80) == 0x7f);
95     assert(hbmask!ulong(0x80_00_00_00_00_00_00_00UL)
96             ==          0x7f_ff_ff_ff_ff_ff_ff_ffUL);
97     assert(hbmask! long(0x80_00_00_00_00_00_00_00UL)
98             ==          0x7f_ff_ff_ff_ff_ff_ff_ffUL);
99 }
100 
101 template dumb(I, string m, string op) {
102     static assert(m == "max" || m == "min");
103     static assert(op == "&" || op == "|" || op == "^");
104     enum cmp = ((m == "max") ? ">" : "<");
105 
106     I dumb(I amin, I amax, I bmin, I bmax) {
107         assert(amin <= amax);
108         assert(bmin <= bmax);
109         static if(m == "max") {
110             I x = I.min;
111         }else{
112             I x = I.max;
113         }
114         for(I a = amin;; a++) {
115             for(I b = bmin;; b++) {
116                 I n = mixin("cast(I)(a"~op~"b)");
117                 if(mixin("n"~cmp~"x")) x = n;
118                 if(b == bmax) break;
119             }
120             if(a == amax) break;
121         }
122         return x;
123     }
124 }
125 
126 unittest{
127     assert(dumb!(uint, "max", "|")(0,8,5,6) == 14);
128     assert(dumb!(uint, "min", "|")(0,8,5,6) == 5);
129 }
130 
131 enum vst0 = q{
132     I r1 = mf(amin, amax, bmin, bmax);
133     I r2 = dumb!(I,m,op)(amin, amax, bmin, bmax);
134     if (r1 != r2) {
135         writefln("Failed at a min=%s max=%s b min=%s max=%s",
136                 amin, amax, bmin, bmax);
137         writefln("\t a min: %8b max:%8b", amin, amax);
138         writefln("\t b min: %8b max:%8b", bmin, bmax);
139         writefln("\t proposed: %8b", r1);
140         writefln("\t verified: %8b", r2);
141     }
142 };
143 enum chkassert = q{
144     I r1 = mf(amin, amax, bmin, bmax);
145     I r2 = dumb!(I,m,op)(amin, amax, bmin, bmax);
146     assert(r1 == r2, 
147             to!string(amin) ~ " " ~ 
148             to!string(amax) ~ " " ~ 
149             to!string(bmin) ~ " " ~ 
150             to!string(bmax));
151 };
152 enum vst2 = q{
153     I r1 = mf(amin, amax, bmin, bmax);
154 };
155 template iter(I, string m, string op, string visitmethod = vst0) 
156     if(isIntegral!I) {
157     static assert(m == "max" || m == "min");
158     static assert(op == "|" || op == "&" || op == "^");
159     static if(m == "max") {
160         static if(op == "&") alias maxAnd mf;
161         else static if(op == "|") alias maxOr mf;
162         else static if(op == "^") alias maxXor mf;
163     }else static if (m == "min") {
164         static if(op == "&") alias minAnd mf;
165         else static if(op == "|") alias minOr mf;
166         else static if(op == "^") alias minXor mf;
167     }
168     static if(isSigned!I) {
169         I maxmin0 = -32;
170         I maxmax0 =  32;
171         I minmin0 = -32;
172     }else{
173         I maxmin0 =   0;
174         I maxmax0 =  64;
175         I minmin0 =   0;
176     }
177     void outer(I maxmin = maxmin0, I maxmax = maxmax0, I minmin = minmin0)() {
178         inner!(maxmin,maxmax,minmin)([0,0,0,0],0);
179     }
180     /// mm = [maxa,maxb,mina,minb]
181     void inner(I maxmin,I maxmax,I minmin)(I[] mm, size_t i) {
182         if(i == 4) {
183             I amin =mm[2], amax = mm[0], bmin = mm[3], bmax = mm[1];
184             mixin(visitmethod);
185         }else if(i < 2) {
186             // max
187             for(mm[i] = maxmin; mm[i] <= maxmax; mm[i]++) {
188                 inner!(maxmin,maxmax,minmin)(mm, i+1);
189             }
190         }else{
191             // min
192             for(mm[i] = minmin; mm[i] <= mm[i-2]; mm[i]++) {
193                 inner!(maxmin,maxmax,minmin)(mm,i+1);
194             }
195         }
196     }
197 
198 }
199 
200 I maxAnd(I)(I amin, I amax, I bmin, I bmax) if(isIntegral!I)
201 in{
202     assert(amin <= amax);
203     assert(bmin <= bmax);
204 }body{
205     static if(isSigned!I) {
206         // ensure I.min is what we think it is
207         static assert(I.min == cast(I)((cast(I)1) << (8*I.sizeof-1)));
208         // ie. highbit = 1, others = 0
209         static if(is(I == byte)) static assert(byte.min == cast(byte) 0x80);
210 
211         I a0 = cast(I) (amin & ~amax &  bmax & I.min);
212         I a1 = cast(I) (amin & ~amax & ~bmin & I.min);
213         I b0 = cast(I) (bmin & ~bmax &  amax & I.min);
214         I b1 = cast(I) (bmin & ~bmax & ~amin & I.min);
215         I ab = cast(I) (amin & ~amax & bmin & ~bmax & I.min);
216         if( a1 || (ab && amax < bmax)) amax = cast(I) -1;
217         if( a0 || (ab && amax >=bmax)) amin = cast(I) 0;
218         if( b1 || (ab && amax >=bmax)) bmax = cast(I) -1;
219         if( b0 || (ab && amax < bmax)) bmin = cast(I) 0;
220         return cast(I) maxAnd!(unsigned!I)(amin, amax, bmin, bmax);
221     }else{
222         I xa1 = ~amin& amax      & bmax;
223         I xa0 = ~amin& amax      &~bmax;
224         I xb1 =        amax&~bmin& bmax;
225         I xb0 =       ~amax&~bmin& bmax;
226         xa0 |= hbmask!I(xa1)&amax&~bmax;
227         xb0 |= hbmask!I(xb1)&bmax&~amax;
228         if(xa0 > xb0) amax |= hbmask!I(xa0);
229         else bmax |= hbmask!I(xb0);
230         return amax&bmax;
231     }
232 }
233 
234 unittest{
235     assert(maxAnd!int(-1,0,-1,0) == 0);
236     assert(maxAnd!int(-1,0,-1,1) == 1);
237     assert(maxAnd!byte(0,8,5,6) == 6);
238     iter!(byte, "max", "&", chkassert).outer!(-16,16,-16);
239     iter!(ubyte, "max", "&", chkassert).outer!(0x7f,0x8f,0x7f);
240     iter!(int, "max", "&", chkassert).outer!(-16,16,-16);
241     iter!(uint, "max", "&", chkassert).outer!(0x7fffffff,0x8000000f,0x7fffffff);
242     iter!(long, "max", "&", chkassert).outer!(-16,16,-16);
243     iter!(ulong, "max", "&", chkassert).outer!(0x7fffffffffffffff,0x800000000000000f,0x7fffffffffffffff);
244 }
245 
246 I maxOr(I)(I amin, I amax, I bmin, I bmax) if(isIntegral!I)
247 in{
248     assert(amin <= amax);
249     assert(bmin <= bmax);
250 }body{
251     static if(isSigned!I) {
252         // ensure I.min is what we think it is
253         static assert(I.min == cast(I)((cast(I)1) << (8*I.sizeof-1)));
254         // ie. highbit = 1, others = 0
255         static if(is(I == byte)) static assert(byte.min == cast(byte) 0x80);
256 
257         I a1 = cast(I) ((amin & ~amax &  bmax) & I.min);
258         I a0 = cast(I) ((amin & ~amax & ~bmax) & I.min);
259         I b1 = cast(I) ((bmin & ~bmax &  amax) & I.min);
260         I b0 = cast(I) ((bmin & ~bmax & ~amax) & I.min);
261         if( a1 ) amax = -1;
262         if( a0 ) amin = 0;
263         if( b1 ) bmax = -1;
264         if( b0 ) bmin = 0;
265         return cast(I) maxOr!(unsigned!I)(amin, amax, bmin, bmax);
266     }else{
267         I x1 = (~amin&amax& bmax)|(~bmin&bmax& amax);
268         I x0 = (~amin&amax&~bmax)|(~bmin&bmax&~amax);
269         x1 |= hbmask(x0)&amax&bmax;
270         return amax|bmax|hbmask(x1);
271     }
272 }
273 
274 unittest{
275     assert(maxOr!byte(0,8,5,6) == 14);
276     iter!(byte, "max", "|", chkassert).outer!(-16,16,-16);
277     iter!(ubyte, "max", "|", chkassert).outer!(0x7f,0x8f,0x7f);
278     iter!(int, "max", "|", chkassert).outer!(-16,16,-16);
279     iter!(uint, "max", "|", chkassert).outer!(0x7fffffff,0x8000000f,0x7fffffff);
280     iter!(long, "max", "|", chkassert).outer!(-16,16,-16);
281     iter!(ulong, "max", "|", chkassert).outer!(0x7fffffffffffffff,0x800000000000000f,0x7fffffffffffffff);
282 }
283 
284 I minAnd(I)(I amin, I amax, I bmin, I bmax) if(isIntegral!I)
285 in{
286     assert(amin <= amax);
287     assert(bmin <= bmax);
288 }body{
289     return ~maxOr!I(~amax, ~amin, ~bmax, ~bmin);
290 }
291 
292 unittest{
293     assert(minAnd!byte(0,8,5,6) == 0);
294     iter!(byte, "min", "&", chkassert).outer!(-16,16,-16);
295     iter!(ubyte, "min", "&", chkassert).outer!(0x7f,0x8f,0x7f);
296     iter!(int, "min", "&", chkassert).outer!(-16,16,-16);
297     iter!(uint, "min", "&", chkassert).outer!(0x7fffffff,0x8000000f,0x7fffffff);
298     iter!(long, "min", "&", chkassert).outer!(-16,16,-16);
299     iter!(ulong, "min", "&", chkassert).outer!(0x7fffffffffffffff,0x800000000000000f,0x7fffffffffffffff);
300 }
301 
302 I minOr(I)(I amin, I amax, I bmin, I bmax) if(isIntegral!I)
303 in{
304     assert(amin <= amax);
305     assert(bmin <= bmax);
306 }body{
307     return ~maxAnd!I(~amax, ~amin, ~bmax, ~bmin);
308 }
309 
310 unittest{
311     assert(minOr!byte(0,8,5,6) == 5);
312     iter!(byte, "min", "|", chkassert).outer!(-16,16,-16);
313     iter!(ubyte, "min", "|", chkassert).outer!(0x7f,0x8f,0x7f);
314     iter!(int, "min", "|", chkassert).outer!(-16,16,-16);
315     iter!(uint, "min", "|", chkassert).outer!(0x7fffffff,0x8000000f,0x7fffffff);
316     iter!(long, "min", "|", chkassert).outer!(-16,16,-16);
317     iter!(ulong, "min", "|", chkassert).outer!(0x7fffffffffffffff,0x800000000000000f,0x7fffffffffffffff);
318 }
319 
320 void writeranges(I)(I amin, I amax, I bmin, I bmax) {
321     writefln("amin:%032b (%s)",amin,I.stringof);
322     writefln("amin:%32s",amin);
323     writefln("amax:%032b (%s)",amax,I.stringof);
324     writefln("amax:%32s",amax);
325     writefln("bmin:%032b (%s)",bmin,I.stringof);
326     writefln("bmin:%32s",bmin);
327     writefln("bmax:%032b (%s)",bmax,I.stringof);
328     writefln("bmax:%32s",bmax);
329 }
330 
331 I maxXor(I)(I amin, I amax, I bmin, I bmax) if(isIntegral!I)
332 in{
333     assert(amin <= amax);
334     assert(bmin <= bmax);
335 }body{
336     static if(isSigned!I) {
337         // ensure I.min is what we think it is
338         static assert(I.min == cast(I)((cast(I)1) << (8*I.sizeof-1)));
339         // ie. highbit = 1, others = 0
340         static if(is(I == byte)) static assert(byte.min == cast(byte) 0x80);
341 
342         debug(ReallyVerbose) {
343             writeranges(amin,amax,bmin,bmax);
344         }
345         I a0 = cast(I)( amin &~amax & ~bmin & I.min);
346         I a1 = cast(I)( amin &~amax &  bmax & I.min);
347         I b0 = cast(I)( bmin &~bmax & ~amin & I.min);
348         I b1 = cast(I)( bmin &~bmax &  amax & I.min);
349         I ab = cast(I)( amin &~amax & bmin &~bmax & I.min);
350         if( ab ) {
351             return max(
352                     maxXor!(unsigned!I)(amin,cast(I) -1, bmin, cast(I) -1),
353                     maxXor!(unsigned!I)(0,amax, 0, bmax));
354         }
355         if( a0 ) amin = cast(I) 0;
356         if( a1 ) amax = cast(I) -1;
357         if( b0 ) bmin = cast(I) 0;
358         if( b1 ) bmax = cast(I) -1;
359         debug(ReallyVerbose) {
360             writeranges(amin,amax,bmin,bmax);
361         }
362         return maxXor!(unsigned!I)(amin,amax,bmin,bmax);
363     }else{
364         I xa00 = (~amin& amax&~bmin&~bmax);
365         I xb00 = (~amin&~amax&~bmin& bmax);
366         I xa11 = (~amin& amax& bmin& bmax);
367         I xb11 = ( amin& amax&~bmin& bmax);
368         I xab  = (~amin& amax&~bmin& bmax);
369         I xia  = xa00 | (hbmask(xb00)&~amin& amax&~bmax) 
370                       | (hbmask(xa11)&~amin&~bmin&~bmax);
371         I xib  = xb00 | (hbmask(xa00)&~bmin& bmax&~amax) 
372                       | (hbmask(xb11)&~bmin&~amin&~amax);
373         I xja  = xa11 | (hbmask(xa00)& amax& bmin& bmax) 
374                       | (hbmask(xb11)&~amin& amax& bmin);
375         I xjb  = xb11 | (hbmask(xb00)& bmax& amin& amax) 
376                       | (hbmask(xa11)&~bmin& bmax& amin);
377         I xk   = xab  | (hbmask(xia )& amax&~bmin& bmax)
378                       | (hbmask(xib )& bmax&~amin& amax)
379                       | (hbmask(xja )&~amin& amax&~bmin)
380                       | (hbmask(xjb )&~bmin& bmax&~amin);
381         amin &= ~hbmask(xia);
382         bmax |=  hbmask(xjb);
383         bmin &= ~hbmask(xib);
384         amax |=  hbmask(xja);
385         return (amin ^ bmax) | (amax ^ bmin) | hbmask(xk);
386     }
387 }
388 
389 unittest{
390     assert(maxXor!byte(0,8,5,6) == 14);
391     assert(maxXor!int(0,8,5,6) == 14);
392     assert(maxXor!uint(0,8,5,6) == 14);
393     assert(maxXor!long(0,8,5,6) == 14);
394     assert(maxXor!long(-1,0,-1,1) == 1);
395     iter!(byte, "max", "^", chkassert).outer!(-16,16,-16);
396     iter!(ubyte, "max", "^", chkassert).outer!(0x7f,0x8f,0x7f);
397     iter!(int, "max", "^", chkassert).outer!(-16,16,-16);
398     iter!(uint, "max", "^", chkassert).outer!(0x7fffffff,0x8000000f,0x7fffffff);
399     iter!(long, "max", "^", chkassert).outer!(-16,16,-16);
400     iter!(ulong, "max", "^", chkassert).outer!(0x7fffffffffffffff,0x800000000000000f,0x7fffffffffffffff);
401 }
402 
403 I minXor(I)(I amin, I amax, I bmin, I bmax) if(isIntegral!I)
404 in{
405     assert(amin <= amax);
406     assert(bmin <= bmax);
407 }body{
408     static if(isSigned!I) {
409         // ensure I.min is what we think it is
410         static assert(I.min == cast(I)((cast(I)1) << (8*I.sizeof-1)));
411         // ie. highbit = 1, others = 0
412         static if(is(I == byte)) static assert(byte.min == cast(byte) 0x80);
413 
414         /+
415         I a0 = cast(I)(amin & ~amax &  bmax & I.min);
416         I a1 = cast(I)(amin & ~amax & ~bmin & I.min);
417         I b0 = cast(I)(bmin & ~bmax &  amax & I.min);
418         I b1 = cast(I)(bmin & ~bmax & ~amin & I.min);
419         I ab = cast(I)(amin & ~amax &  bmin & ~bmax & I.min);
420         +/
421         if( amin < 0 && amax >= 0 && bmin < 0 && bmax >= 0 ) {
422             return min( minXor!(unsigned!I)(0,amax,bmin, cast(I)-1),
423                         minXor!(unsigned!I)(amin,cast(I)-1,0,bmax));
424         }
425         if( amin < 0 && amax >= 0 && bmax <  0) amin =  0;
426         if( amin < 0 && amax >= 0 && bmin >= 0) amax = -1;
427         if( bmin < 0 && bmax >= 0 && amax <  0) bmin =  0;
428         if( bmin < 0 && bmax >= 0 && amin >= 0) bmax = -1;
429         return minXor!(unsigned!I)(amin,amax,bmin,bmax);
430     }else{
431         I xa00 = (~amin& amax&~bmin&~bmax);
432         I xb00 = (~amin&~amax&~bmin& bmax);
433         I xa11 = (~amin& amax& bmin& bmax);
434         I xb11 = ( amin& amax&~bmin& bmax);
435         I xab  = (~amin& amax&~bmin& bmax);
436         I xa00a11 = (hbmask(xa00)&~amin&       bmin& bmax);
437         I xa00b11 = (hbmask(xa00)& amin&      ~bmin& bmax);
438         I xb00a11 = (hbmask(xb00)&~amin& amax& bmin      );
439         I xb00b11 = (hbmask(xb00)& amin& amax&~bmin      );
440         I xa11a00 = (hbmask(xa11)      & amax&~bmin&~bmax);
441         I xb11a00 = (hbmask(xb11)&~amin& amax      &~bmax);
442         I xa11b00 = (hbmask(xa11)      &~amax&~bmin& bmax);
443         I xb11b00 = (hbmask(xb11)&~amin&~amax      & bmax);
444         I xia  = xa11 | xa00a11 | xb00a11;
445         I xib  = xb11 | xa00b11 | xb00b11;
446         I xja  = xa00 | xa11a00 | xb11a00; 
447         I xjb  = xb00 | xa11b00 | xb11b00;
448 
449         I xk   = xab  | (hbmask(xa00)&~amin&      ~bmin& bmax)
450                       | (hbmask(xb00)&~amin& amax&~bmin)
451                       | (hbmask(xa11)      & amax&~bmin& bmax)
452                       | (hbmask(xb11)&~amin& amax      & bmax)
453 
454                       | (hbmask(xa00a11|xa11a00)            &~bmin& bmax)
455                       | (hbmask(xa00b11|xb11a00)&~amin            & bmax)
456                       | (hbmask(xb00a11|xa11b00)      & amax&~bmin      )
457                       | (hbmask(xb00b11|xb11b00)&~amin& amax            );
458 
459         if (xia > xib) {
460             amin &= ~hbmask(xia);
461         }else{
462             bmin &= ~hbmask(xib);
463         }
464         if (xja > xjb) {
465             amax |=  hbmask(xja);
466         }else {
467             bmax |=  hbmask(xjb);
468         }
469         return (amin ^ bmin) & (amax ^ bmax) & ~hbmask(xk);
470     }
471 }
472 
473 unittest{
474     assert(minXor!long(0,0,-32,0) == -32);
475     iter!(byte, "min", "^", chkassert).outer!(-16,16,-16);
476     iter!(ubyte, "min", "^", chkassert).outer!(0x7f,0x8f,0x7f);
477     iter!(int, "min", "^", chkassert).outer!(-16,16,-16);
478     iter!(uint, "min", "^", chkassert).outer!(0x7fffffff,0x8000000f,0x7fffffff);
479     iter!(long, "min", "^", chkassert).outer!(-16,16,-16);
480     iter!(ulong, "min", "^", chkassert).outer!(0x7fffffffffffffff,0x800000000000000f,0x7fffffffffffffff);
481 }
482