10

What is the best way to convert binary bits (it might be a list of 0/1, for example) into numbers in a reversible way. I've written a native predicate in swi, but is there better solution ? Best regards

false
  • 10,533
  • 12
  • 98
  • 192
  • What should be the answer for the following query: `binary_number(B, -5).`: an exception like *Domain error: \`not_less_than_zero' expected, found \`-5'* **or** failure (`no` / `false`)? – Tudor Berariu Jan 14 '15 at 19:22
  • @TudorBerariu: As you like. Both failure and some error is fine. (BTW; I did not read your question before, you need to @ me) – false Jan 16 '15 at 18:04

4 Answers4

11

Use CLP(FD) constraints, for example:

:- use_module(library(clpfd)).

binary_number(Bs0, N) :-
        reverse(Bs0, Bs),
        foldl(binary_number_, Bs, 0-0, _-N).

binary_number_(B, I0-N0, I-N) :-
        B in 0..1,
        N #= N0 + B*2^I0,
        I #= I0 + 1.

Example queries:

?- binary_number([1,0,1], N).
N = 5.

?- binary_number(Bs, 5).
Bs = [1, 0, 1] .

?- binary_number(Bs, N).
Bs = [],
N = 0 ;
Bs = [N],
N in 0..1 ;
etc.
mat
  • 40,080
  • 3
  • 46
  • 74
  • 1
    `binary_number(Bs, 5).` does not terminate. – false Jan 05 '15 at 22:14
  • That is to be expected: In this representation, using a list of 0 and 1 for binary numbers, an arbitrary number of "0" can be prepended to the list while still denoting the same integer. – mat Jan 06 '15 at 12:36
  • OP asked for a reversible predicate. In any case, `binary_number([1|_],1)` has no leading zeros whatsoever. – false Jan 06 '15 at 16:14
  • It is the requirement for reversibility that makes this behaviour necessary. Suppose `Bs = [1,0,1]` were the only solution for `binary_number(Bs, 5)`. Thus, `Bs = [0,0,0,1,0,1], binary_number(Bs, 5)` would succeed, but exchanging the goals by commutativity of conjunction would fail, making the predicate *not* reversible. – mat Jan 06 '15 at 17:30
  • See [this answer](http://stackoverflow.com/a/28442760/772868) for a solution that is - as much as (probably) possible - reversible. – false Jun 07 '15 at 10:01
7

Here is the solution I was thinking of, or rather what I hoped exists.

:- use_module(library(clpfd)).

binary_number(Bs, N) :-
   binary_number_min(Bs, 0,N, N).

binary_number_min([], N,N, _M).
binary_number_min([B|Bs], N0,N, M) :-
   B in 0..1,
   N1 #= B+2*N0,
   M #>= N1,
   binary_number_min(Bs, N1,N, M).

This solution also terminates for queries like:

?- Bs = [1|_], N #=< 5, binary_number(Bs, N).
false
  • 10,533
  • 12
  • 98
  • 192
  • 2
    This is an elegant, simple way around the termination issue (+1) and avoids the exponentiation (:)). – lurker Feb 14 '15 at 14:44
  • I don't understand the purpose of `M`. Can't you remove it and replace it in `M #>= N1` by `N`? – Fatalize Apr 21 '16 at 19:00
  • @Fatalize: `M`, thus the 4th argument is needed to ensure that the predicate is really reversible. It is the original variable... – false Apr 21 '16 at 19:45
4

The solution

This answer seeks to provide a predicate binary_number/2 that presents both and the best termination properties. I've used when/2 in order to stop queries like canonical_binary_number(B, 10) from going into infinite looping after finding the first (unique) solution. There is a trade-off, of course, the program has redundant goals now.

canonical_binary_number([0], 0).
canonical_binary_number([1], 1).
canonical_binary_number([1|Bits], Number):-
    when(ground(Number),
         (Number > 1,
          Pow is floor(log(Number) / log(2)),
          Number1 is Number - 2 ^ Pow,
          (   Number1 > 1
           -> Pow1 is floor(log(Number1) / log(2)) + 1
           ;  Pow1 = 1
         ))),
    length(Bits, Pow),
    between(1, Pow, Pow1),
    length(Bits1, Pow1),
    append(Zeros, Bits1, Bits),
    maplist(=(0), Zeros),
    canonical_binary_number(Bits1, Number1),
    Number is Number1 + 2 ^ Pow.

binary_number(Bits, Number):-
    canonical_binary_number(Bits, Number).
binary_number([0|Bits], Number):-
    binary_number(Bits, Number).

Purity and termination

I claim that this predicate presents from construction. I hope I got it right from these answers: one, two and three.

Any goal with proper arguments terminates. If arguments need to be checked, the simplest way to achieve this is using the built-in length/2:

binary_number(Bits, Number):-
    length(_, Number),
    canonical_binary_number(Bits, Number).

?- binary_number(Bits, 2+3).
ERROR: length/2: Type error: `integer' expected, found `2+3'
   Exception: (6) binary_number(_G1642009, 2+3) ? abort
% Execution Aborted
?- binary_number(Bits, -1).
ERROR: length/2: Domain error: `not_less_than_zero' expected, found `-1'
   Exception: (6) binary_number(_G1642996, -1) ? creep

Example queries

?- binary_number([1,0,1|Tail], N).
Tail = [],
N = 5 ;
Tail = [0],
N = 10 ;
Tail = [1],
N = 11 ;
Tail = [0, 0],
N = 20 .

?- binary_number(Bits, 20).
Bits = [1, 0, 1, 0, 0] ;
Bits = [0, 1, 0, 1, 0, 0] ;
Bits = [0, 0, 1, 0, 1, 0, 0] ;
Bits = [0, 0, 0, 1, 0, 1, 0, 0] ;
Bits = [0, 0, 0, 0, 1, 0, 1, 0, 0] .

?- binary_number(Bits, N).
Bits = [0],
N = 0 ;
Bits = [1],
N = 1 ;
Bits = [1, 0],
N = 2 ;
Bits = [1, 1],
N = 3 ;
Bits = [1, 0, 0],
N = 4 ;
Bits = [1, 0, 1],
N = 5 .
Community
  • 1
  • 1
Tudor Berariu
  • 4,890
  • 2
  • 16
  • 29
1

playing with bits...

binary_number(Bs, N) :-
    var(N) -> foldl(shift, Bs, 0, N) ; bitgen(N, Rs), reverse(Rs, Bs).

shift(B, C, R) :-
    R is (C << 1) + B.

bitgen(N, [B|Bs]) :-
    B is N /\ 1 , ( N > 1 -> M is N >> 1, bitgen(M, Bs) ; Bs = [] ).
CapelliC
  • 58,738
  • 5
  • 44
  • 87