[m-rev.] for review: fix problems with empty bitmaps

Peter Wang novalazy at gmail.com
Mon Mar 1 17:44:30 AEDT 2010


Branches: main

Fix bitmap predicates which did not work correctly with empty bitmaps.

Note that `bitmap.to_string' now returns "<0:>" for an empty bitmap instead
of "<0:00>".

library/bitmap.m:
        Add `in_range_rexcl' to check an index is in the range [0, num_bits).

        Fix bounds checks on empty bitmaps in `^ bits' and `copy_bytes'.

        Simplify other bounds checks using `in_range_rexcl'.

        Make `byte_index_for_bit' return -1 if its argument is negative,
        instead of 0.  `byte_index_for_bit(NumBits - 1)' is used to get the
        last byte index, so now loops over empty bitmaps will stop immediately
        as the initial index must be greater than -1.

        Make some code neater.

tests/hard_coded/Mmakefile:
tests/hard_coded/bitmap_empty.exp:
tests/hard_coded/bitmap_empty.m:
        Add a test case.

diff --git a/library/bitmap.m b/library/bitmap.m
index f17fa4d..8007c16 100644
--- a/library/bitmap.m
+++ b/library/bitmap.m
@@ -553,6 +553,11 @@ initialize_bitmap_bytes(BM, ByteIndex, LastByteIndex, Init) =
 
 in_range(BM, I) :- 0 =< I, I < num_bits(BM).
 
+:- pred in_range_rexcl(bitmap, bit_index).
+:- mode in_range_rexcl(in, in) is semidet.
+
+in_range_rexcl(BM, I) :- 0 =< I, I =< num_bits(BM).
+
 byte_in_range(BM, I) :-
     in_range(BM, I * bits_per_byte + bits_per_byte - 1).
 
@@ -581,9 +586,9 @@ BM ^ unsafe_bit(I) =
 BM ^ bits(FirstBit, NumBits) =
     ( if
         FirstBit >= 0,
-        in_range(BM, FirstBit + NumBits - 1),
         NumBits >= 0,
-        NumBits =< int.bits_per_int
+        NumBits =< int.bits_per_int,
+        in_range_rexcl(BM, FirstBit + NumBits)
       then
         BM ^ unsafe_bits(FirstBit, NumBits)
       else if
@@ -591,8 +596,8 @@ BM ^ bits(FirstBit, NumBits) =
         ; NumBits > int.bits_per_int
         )
       then
-        throw_bitmap_error(
-    "bitmap.bits: number of bits must be between 0 and `int.bits_per_int'.")
+        throw_bitmap_error("bitmap.bits: number of bits must be between " ++
+            "0 and `int.bits_per_int'.")
       else
         throw_bounds_error(BM, "bitmap.bits", FirstBit)
     ).
@@ -644,14 +649,9 @@ extract_bits_from_byte_index(ByteIndex, FirstBitIndex,
 (BM ^ bits(FirstBit, NumBits) := Bits) =
     ( if
         FirstBit >= 0,
-        (
-            NumBits >= 0,
-            NumBits =< int.bits_per_int,
-            in_range(BM, FirstBit + NumBits - 1)
-        ;
-            NumBits = 0,
-            in_range(BM, FirstBit)
-        )
+        NumBits >= 0,
+        NumBits =< int.bits_per_int,
+        in_range_rexcl(BM, FirstBit + NumBits)
       then
         BM ^ unsafe_bits(FirstBit, NumBits) := Bits
       else if
@@ -706,19 +706,17 @@ set_bits_in_byte_index(ByteIndex, LastBitIndex,
 %-----------------------------------------------------------------------------%
 
 :- type bitmap.slice
-    ---> bitmap.slice_ctor(
-            slice_bitmap_field :: bitmap,
-            slice_start_bit_index_field :: bit_index,
-            slice_num_bits_field :: num_bits
-    ).
+    --->    bitmap.slice_ctor(
+                slice_bitmap_field          :: bitmap,
+                slice_start_bit_index_field :: bit_index,
+                slice_num_bits_field        :: num_bits
+            ).
 
 slice(BM, StartBit, NumBits) = Slice :-
     ( if
         NumBits >= 0,
         StartBit >= 0,
-        ( in_range(BM, StartBit + NumBits - 1)
-        ; NumBits = 0, in_range(BM, StartBit)
-        )
+        in_range_rexcl(BM, StartBit + NumBits)
       then
         Slice = bitmap.slice_ctor(BM, StartBit, NumBits)
       else
@@ -741,10 +739,9 @@ Slice ^ slice_num_bytes =
 
 :- func quotient_bits_per_byte_with_rem_zero(string, int) = int is det.
 
-quotient_bits_per_byte_with_rem_zero(Pred, Int) =
-            Int `unchecked_quotient` bits_per_byte :-
-    ( Int `unchecked_rem` bits_per_byte = 0 ->
-        true
+quotient_bits_per_byte_with_rem_zero(Pred, Int) = Quotient :-
+    ( unchecked_rem(Int, bits_per_byte) = 0 ->
+        Quotient = unchecked_quotient(Int, bits_per_byte)
     ;
         throw_bitmap_error(Pred ++ ": not a byte slice.")
     ).
@@ -777,17 +774,23 @@ flip(I, BM, flip(BM, I)).
 
 %-----------------------------------------------------------------------------%
 
-unsafe_set(BM, I) =
-    BM ^ unsafe_byte(byte_index_for_bit(I)) :=
-        BM ^ unsafe_byte(byte_index_for_bit(I)) \/ bitmask(I).
+unsafe_set(BM0, I) = BM :-
+    ByteIndex = byte_index_for_bit(I),
+    Byte0 = BM0 ^ unsafe_byte(ByteIndex),
+    Byte = Byte0 \/ bitmask(I),
+    BM = BM0 ^ unsafe_byte(ByteIndex) := Byte.
 
-unsafe_clear(BM, I) =
-    BM ^ unsafe_byte(byte_index_for_bit(I)) :=
-        BM ^ unsafe_byte(byte_index_for_bit(I)) /\ \bitmask(I).
+unsafe_clear(BM0, I) = BM :-
+    ByteIndex = byte_index_for_bit(I),
+    Byte0 = BM0 ^ unsafe_byte(ByteIndex),
+    Byte = Byte0 /\ \bitmask(I),
+    BM = BM0 ^ unsafe_byte(ByteIndex) := Byte.
 
-unsafe_flip(BM, I) =
-    BM ^ unsafe_byte(byte_index_for_bit(I)) :=
-        BM ^ unsafe_byte(byte_index_for_bit(I)) `xor` bitmask(I).
+unsafe_flip(BM0, I) = BM :-
+    ByteIndex = byte_index_for_bit(I),
+    Byte0 = BM0 ^ unsafe_byte(ByteIndex),
+    Byte = Byte0 `xor` bitmask(I),
+    BM = BM0 ^ unsafe_byte(ByteIndex) := Byte.
 
 unsafe_set(I, BM, unsafe_set(BM, I)).
 
@@ -833,11 +836,15 @@ complement(BM) =
 :- func complement_2(int, bitmap) = bitmap.
 :- mode complement_2(in, bitmap_di) = bitmap_uo is det.
 
-complement_2(ByteI, BM) =
-    ( if ByteI < 0
-      then BM
-      else complement_2(ByteI - 1,
-            BM ^ unsafe_byte(ByteI) := \ (BM ^ unsafe_byte(ByteI)))
+complement_2(ByteI, BM0) = BM :-
+    ( if
+        ByteI < 0
+      then
+        BM = BM0
+      else
+        X = BM0 ^ unsafe_byte(ByteI),
+        BM1 = BM0 ^ unsafe_byte(ByteI) := \ X,
+        BM = complement_2(ByteI - 1, BM1)
     ).
 
 %-----------------------------------------------------------------------------%
@@ -889,7 +896,8 @@ xor(BMa, BMb) =
     in, bitmap_di) = bitmap_uo is det.
 
 zip(Fn, BMa, BMb) =
-    ( if num_bits(BMb) = 0 then BMb
+    ( if num_bits(BMb) = 0
+      then BMb
       else zip2(byte_index_for_bit(num_bits(BMb) - 1), Fn, BMa, BMb)
     ).
 
@@ -900,13 +908,14 @@ zip(Fn, BMa, BMb) =
 :- mode zip2(in, func(in, in) = out is det,
     in, bitmap_di) = bitmap_uo is det.
 
-zip2(I, Fn, BMa, BMb) =
+zip2(I, Fn, BMa, BMb) = BM :-
     ( if I >= 0 then
-        zip2(I - 1, Fn, BMa,
-            BMb ^ unsafe_byte(I) :=
-                Fn(BMa ^ unsafe_byte(I), BMb ^ unsafe_byte(I)))
+        Xa = BMa ^ unsafe_byte(I),
+        Xb = BMb ^ unsafe_byte(I),
+        BMc = BMb ^ unsafe_byte(I) := Fn(Xa, Xb),
+        BM = zip2(I - 1, Fn, BMa, BMc)
       else
-        BMb
+        BM = BMb
     ).
 
 %-----------------------------------------------------------------------------%
@@ -941,12 +950,8 @@ copy_bits(SameBM, SrcBM, SrcStartBit, DestBM, DestStartBit, NumBits) =
         NumBits >= 0,
         SrcStartBit >= 0,
         DestStartBit >= 0,
-        ( in_range(SrcBM, SrcStartBit + NumBits - 1)
-        ; NumBits = 0, in_range(SrcBM, SrcStartBit)
-        ),
-        ( in_range(DestBM, DestStartBit + NumBits - 1)
-        ; NumBits = 0, in_range(DestBM, DestStartBit)
-        )
+        in_range_rexcl(SrcBM, SrcStartBit + NumBits),
+        in_range_rexcl(DestBM, DestStartBit + NumBits)
       then
         unsafe_copy_bits(SameBM, SrcBM, SrcStartBit,
             DestBM, DestStartBit, NumBits)
@@ -1105,8 +1110,12 @@ copy_bytes_in_bitmap(SrcBM, SrcStartByteIndex, DestStartByteIndex, NumBytes) =
     bitmap_di, in, in) = bitmap_uo is det.
 
 copy_bytes(SameBM, SrcBM, SrcStartByte, DestBM, DestStartByte, NumBytes) =
-   ( if
-        NumBytes >= 0,
+    ( if
+        NumBytes = 0
+      then
+        DestBM
+      else if
+        NumBytes > 0,
         SrcStartByte >= 0,
         byte_in_range(SrcBM, SrcStartByte + NumBytes - 1),
         DestStartByte >= 0,
@@ -1387,10 +1396,10 @@ choose_copy_direction(SameBM, SrcStartBit, DestStartBit) =
     %
 to_string(BM) = Str :-
     NumBits = BM ^ num_bits,
-    to_string_chars(byte_index_for_bit(NumBits - 1), BM,
-        [('>')], Chars),
-    Str = string.from_char_list(
-            [('<') | to_char_list(int_to_string(NumBits))] ++ [(':') | Chars]).
+    to_string_chars(byte_index_for_bit(NumBits - 1), BM, ['>'], BitChars),
+    LenChars = to_char_list(int_to_string(NumBits)),
+    Chars = ['<' | LenChars] ++ [':' | BitChars],
+    Str = string.from_char_list(Chars).
 
 :- pred to_string_chars(int, bitmap, list(char), list(char)).
 %:- mode to_string_chars(in, bitmap_ui, in, out) is det.
@@ -1687,10 +1696,17 @@ bytes_equal(Index, MaxIndex, BM1, BM2) :-
 ").
 
 bitmap_compare(Result, BM1, BM2) :-
-    compare(Result0, BM1 ^ num_bits, (BM2 ^ num_bits) @ NumBits),
-    ( if Result0 = (=) then
-        bytes_compare(Result, 0, byte_index_for_bit(NumBits), BM1, BM2)
-      else
+    NumBits1 = BM1 ^ num_bits,
+    NumBits2 = BM2 ^ num_bits,
+    compare(Result0, NumBits1, NumBits2),
+    (
+        Result0 = (=),
+        MaxIndex = byte_index_for_bit(NumBits2),
+        bytes_compare(Result, 0, MaxIndex, BM1, BM2)
+    ;
+        ( Result0 = (<)
+        ; Result0 = (>)
+        ),
         Result = Result0
     ).
 
@@ -1700,7 +1716,9 @@ bitmap_compare(Result, BM1, BM2) :-
 
 bytes_compare(Result, Index, MaxIndex, BM1, BM2) :-
     ( if Index =< MaxIndex then
-        compare(Result0, BM1 ^ unsafe_byte(Index), BM2 ^ unsafe_byte(Index)),
+        Byte1 = BM1 ^ unsafe_byte(Index),
+        Byte2 = BM2 ^ unsafe_byte(Index),
+        compare(Result0, Byte1, Byte2),
         (
             Result0 = (=),
             bytes_compare(Result, Index + 1, MaxIndex, BM1, BM2)
@@ -1732,6 +1750,7 @@ det_num_bytes(BM) = Bytes :-
 %-----------------------------------------------------------------------------%
 
 num_bits(_) = _ :- private_builtin.sorry("bitmap.num_bits").
+
 :- pragma foreign_proc("C",
     num_bits(BM::in) = (NumBits::out),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
@@ -1766,6 +1785,7 @@ num_bits(_) = _ :- private_builtin.sorry("bitmap.num_bits").
 :- mode 'num_bits :='(bitmap_di, in) = bitmap_uo is det.
 
 'num_bits :='(_, _) = _ :- private_builtin.sorry("bitmap.'num_bits :='").
+
 :- pragma foreign_proc("C",
     'num_bits :='(BM0::bitmap_di, NumBits::in) = (BM::bitmap_uo),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
@@ -1960,7 +1980,12 @@ bits_per_byte = 8.
     %
 :- func byte_index_for_bit(bit_index) = byte_index.
 
-byte_index_for_bit(I) = unchecked_quotient(I, bits_per_byte).
+byte_index_for_bit(I) =
+    ( if I < 0 then
+        -1
+      else
+        unchecked_quotient(I, bits_per_byte)
+    ).
 
 %-----------------------------------------------------------------------------%
 
diff --git a/tests/hard_coded/Mmakefile b/tests/hard_coded/Mmakefile
index 17de67a..c058496 100644
--- a/tests/hard_coded/Mmakefile
+++ b/tests/hard_coded/Mmakefile
@@ -556,6 +556,7 @@ ifeq "$(findstring profdeep,$(GRADE))" ""
 		allow_stubs \
 		backend_external \
 		backjump_test \
+		bitmap_empty \
 		bitmap_test \
 		bit_buffer_test \
 		dir_test \
diff --git a/tests/hard_coded/bitmap_empty.exp b/tests/hard_coded/bitmap_empty.exp
new file mode 100644
index 0000000..304b5ca
--- /dev/null
+++ b/tests/hard_coded/bitmap_empty.exp
@@ -0,0 +1,68 @@
+-- new
+"<0:>"
+-- copy
+"<0:>"
+-- resize
+"<0:>"
+"<4:F0>"
+"<0:>"
+-- shrink_without_copying
+"<0:>"
+-- in_range
+ok
+ok
+ok
+-- byte_in_range
+ok
+ok
+ok
+-- num_bits
+0
+-- det_num_bytes
+0
+-- ^bit
+expected: bitmap_error("bitmap.bit: index 0 is out of bounds [0 - 0).")
+-- ^bits
+0
+-- ^bits:=
+"<0:>"
+-- ^byte
+expected: bitmap_error("bitmap.byte: index 0 is out of bounds [0 - 0).")
+-- ^byte:=
+expected: bitmap_error("bitmap.\'byte :=\': index 0 is out of bounds [0 - 0).")
+-- slice
+slice_ctor("<0:>", 0, 0)
+-- byte_slice
+slice_ctor("<0:>", 0, 0)
+-- flip
+expected: bitmap_error("bitmap.flip: index 0 is out of bounds [0 - 0).")
+-- complement
+"<0:>"
+-- union
+"<0:>"
+-- intersect
+"<0:>"
+-- difference
+"<0:>"
+-- xor
+"<0:>"
+-- append_list
+"<2:C0>"
+-- copy_bits
+"<0:>"
+-- copy_bits_in_bitmap
+"<0:>"
+-- copy_bytes
+"<0:>"
+-- copy_bytes_in_bitmap
+"<0:>"
+-- from_string
+"<0:>"
+-- to_byte_string
+<>
+-- hash
+0
+-- bitmap_equal
+equal
+-- bitmap_compare
+'='
diff --git a/tests/hard_coded/bitmap_empty.m b/tests/hard_coded/bitmap_empty.m
new file mode 100644
index 0000000..ac7af06
--- /dev/null
+++ b/tests/hard_coded/bitmap_empty.m
@@ -0,0 +1,296 @@
+%-----------------------------------------------------------------------------%
+% Test operations on empty (zero-length) bitmaps.
+
+:- module bitmap_empty.
+:- interface.
+
+:- import_module io.
+
+:- pred main(io::di, io::uo) is cc_multi.
+
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+
+:- implementation.
+
+:- import_module bitmap.
+:- import_module bool.
+:- import_module list.
+
+%-----------------------------------------------------------------------------%
+
+main(!IO) :-
+    io.write_string("-- new\n", !IO),
+    A0 = bitmap.new(0, no) : bitmap,
+    io.write(A0, !IO),
+    io.nl(!IO),
+
+    io.write_string("-- copy\n", !IO),
+    some [B] (
+        copy(A0, B),
+        io.write(B, !IO),
+        io.nl(!IO)
+    ),
+
+    io.write_string("-- resize\n", !IO),
+    some [B0, B1, B2, B3] (
+        B0 = bitmap.new(0, no),
+        B1 = resize(B0, 0, no),     % no change
+        io.write(B1, !IO),
+        io.nl(!IO),
+        B2 = resize(B1, 4, yes),    % enlarge
+        io.write(B2, !IO),
+        io.nl(!IO),
+        B3 = resize(B2, 0, yes),    % shrink
+        io.write(B3, !IO),
+        io.nl(!IO)
+    ),
+
+    io.write_string("-- shrink_without_copying\n", !IO),
+    some [B0, B1] (
+        B0 = bitmap.new(4, no),
+        B1 = shrink_without_copying(B0, 0),
+        io.write(B1, !IO),
+        io.nl(!IO)
+    ),
+
+    io.write_string("-- in_range\n", !IO),
+    ( in_range(A0, -1) ->
+        io.write_string("error\n", !IO)
+    ;
+        io.write_string("ok\n", !IO)
+    ),
+    ( in_range(A0, 0) ->
+        io.write_string("error\n", !IO)
+    ;
+        io.write_string("ok\n", !IO)
+    ),
+    ( in_range(A0, 1) ->
+        io.write_string("error\n", !IO)
+    ;
+        io.write_string("ok\n", !IO)
+    ),
+
+    io.write_string("-- byte_in_range\n", !IO),
+    ( byte_in_range(A0, -1) ->
+        io.write_string("error\n", !IO)
+    ;
+        io.write_string("ok\n", !IO)
+    ),
+    ( byte_in_range(A0, 0) ->
+        io.write_string("error\n", !IO)
+    ;
+        io.write_string("ok\n", !IO)
+    ),
+    ( byte_in_range(A0, 1) ->
+        io.write_string("error\n", !IO)
+    ;
+        io.write_string("ok\n", !IO)
+    ),
+
+    io.write_string("-- num_bits\n", !IO),
+    NumBits = num_bits(A0),
+    io.write_int(NumBits, !IO),
+    io.nl(!IO),
+
+    io.write_string("-- det_num_bytes\n", !IO),
+    NumBytes = det_num_bytes(A0),
+    io.write_int(NumBytes, !IO),
+    io.nl(!IO),
+
+    io.write_string("-- ^bit\n", !IO),
+    (try []
+        Bit = A0 ^ bit(0)
+    then
+        io.write(Bit, !IO),
+        io.nl(!IO)
+    catch_any BitExcp ->
+        io.write_string("expected: ", !IO),
+        io.write(BitExcp, !IO),
+        io.nl(!IO)
+    ),
+
+    io.write_string("-- ^bits\n", !IO),
+    Bits = A0 ^ bits(0, 0),
+    io.write(Bits, !IO),
+    io.nl(!IO),
+
+    io.write_string("-- ^bits:=\n", !IO),
+    some [B0, B1] (
+        B0 = bitmap.new(0, no),
+        B1 = B0 ^ bits(0, 0) := 0,
+        io.write(B1, !IO),
+        io.nl(!IO)
+    ),
+
+    io.write_string("-- ^byte\n", !IO),
+    (try []
+        Byte = A0 ^ byte(0)
+    then
+        io.write(Byte, !IO),
+        io.nl(!IO)
+    catch_any ByteExcp ->
+        io.write_string("expected: ", !IO),
+        io.write(ByteExcp, !IO),
+        io.nl(!IO)
+    ),
+
+    io.write_string("-- ^byte:=\n", !IO),
+    some [B0, B1] (
+        (try [] (
+            B0 = bitmap.new(0, no),
+            B1 = B0 ^ byte(0) := 0
+        )
+        then
+            io.write(B1, !IO),
+            io.nl(!IO)
+        catch_any SetByteExcp ->
+            io.write_string("expected: ", !IO),
+            io.write(SetByteExcp, !IO),
+            io.nl(!IO)
+        )
+    ),
+
+    io.write_string("-- slice\n", !IO),
+    some [S] (
+        S = bitmap.slice(A0, 0, 0),
+        io.write(S, !IO),
+        io.nl(!IO)
+    ),
+
+    io.write_string("-- byte_slice\n", !IO),
+    some [S] (
+        S = bitmap.byte_slice(A0, 0, 0),
+        io.write(S, !IO),
+        io.nl(!IO)
+    ),
+
+    io.write_string("-- flip\n", !IO),
+    some [B0, B1] (
+        (try [] (
+            B0 = bitmap.new(0, no),
+            B1 = flip(B0, 0)
+        )
+        then
+            io.write(B1, !IO)
+        catch_any E18 ->
+            io.write_string("expected: ", !IO),
+            io.write(E18, !IO),
+            io.nl(!IO)
+        )
+    ),
+
+    A1 = bitmap.new(0, no),
+    A2 = bitmap.new(0, no),
+
+    io.write_string("-- complement\n", !IO),
+    Bcompl = complement(A1),
+    io.write(Bcompl, !IO),
+    io.nl(!IO),
+
+    io.write_string("-- union\n", !IO),
+    Bunion = union(A1, A2),
+    io.write(Bunion, !IO),
+    io.nl(!IO),
+
+    io.write_string("-- intersect\n", !IO),
+    Bintersect = intersect(A1, A2),
+    io.write(Bintersect, !IO),
+    io.nl(!IO),
+
+    io.write_string("-- difference\n", !IO),
+    Bdiff = difference(A1, A2),
+    io.write(Bdiff, !IO),
+    io.nl(!IO),
+
+    io.write_string("-- xor\n", !IO),
+    Bxor = xor(A1, A2),
+    io.write(Bxor, !IO),
+    io.nl(!IO),
+
+    io.write_string("-- append_list\n", !IO),
+    some [B0, B1, B2, B3] (
+        B0 = bitmap.new(1, yes),
+        B1 = bitmap.new(0, yes),
+        B2 = bitmap.new(1, yes),
+        B3 = append_list([B0, B1, B2]),
+        io.write(B3, !IO),
+        io.nl(!IO)
+    ),
+
+    io.write_string("-- copy_bits\n", !IO),
+    some [B0, B1, B2] (
+        B0 = bitmap.new(1, yes),
+        B1 = bitmap.new(0, yes),
+        B2 = copy_bits(B0, 0, B1, 0, 0),
+        io.write(B2, !IO),
+        io.nl(!IO)
+    ),
+
+    io.write_string("-- copy_bits_in_bitmap\n", !IO),
+    some [B0, B1] (
+        B0 = bitmap.new(0, no),
+        B1 = copy_bits_in_bitmap(B0, 0, 0, 0),
+        io.write(B1, !IO),
+        io.nl(!IO)
+    ),
+
+    io.write_string("-- copy_bytes\n", !IO),
+    some [B0, B1, B2] (
+        B0 = bitmap.new(8, yes),
+        B1 = bitmap.new(0, no),
+        B2 = copy_bytes(B0, 0, B1, 0, 0),
+        io.write(B2, !IO),
+        io.nl(!IO)
+    ),
+
+    io.write_string("-- copy_bytes_in_bitmap\n", !IO),
+    some [B0, B1] (
+        B0 = bitmap.new(0, no),
+        B1 = copy_bytes_in_bitmap(B0, 0, 0, 0),
+        io.write(B1, !IO),
+        io.nl(!IO)
+    ),
+
+    io.write_string("-- from_string\n", !IO),
+    String = to_string(A0),
+    ( Bstring = bitmap.from_string(String) ->
+        io.write(Bstring, !IO),
+        io.nl(!IO)
+    ;
+        io.write_string("error\n", !IO)
+    ),
+
+    io.write_string("-- to_byte_string\n", !IO),
+    ByteString = bitmap.to_byte_string(A0),
+    io.write_string("<", !IO),
+    io.write_string(ByteString, !IO),
+    io.write_string(">\n", !IO),
+
+    io.write_string("-- hash\n", !IO),
+    Hash = bitmap.hash(A0),
+    io.write_int(Hash, !IO),
+    io.nl(!IO),
+
+    io.write_string("-- bitmap_equal\n", !IO),
+    some [B0, B1] (
+        B0 = bitmap.new(0, no),
+        B1 = bitmap.new(0, no),
+        ( B0 = B1 ->
+            io.write_string("equal\n", !IO)
+        ;
+            io.write_string("not equal\n", !IO)
+        )
+    ),
+
+    io.write_string("-- bitmap_compare\n", !IO),
+    some [B0, B1] (
+        B0 = bitmap.new(0, no),
+        B1 = bitmap.new(0, no),
+        compare(Compare, B0, B1),
+        io.write(Compare, !IO),
+        io.nl(!IO)
+    ).
+
+%-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=8 sts=4 sw=4 et

--------------------------------------------------------------------------
mercury-reviews mailing list
Post messages to:       mercury-reviews at csse.unimelb.edu.au
Administrative Queries: owner-mercury-reviews at csse.unimelb.edu.au
Subscriptions:          mercury-reviews-request at csse.unimelb.edu.au
--------------------------------------------------------------------------



More information about the reviews mailing list