5

I want to write a predicate that an integer and a list of digits, and succeed if Digits contain the digits of the integer in the proper order, i.e:

?-digit_lists( Num, [1,2,3,4] ).
[Num == 1234].

Here is what I have so far:

my_digits( 0, [] ).
my_digits(N,[A|As]) :- N1 is floor(N/10), A is N mod 10, my_digits(N1, As).
mat
  • 40,498
  • 3
  • 51
  • 78
Duc Hai
  • 51
  • 1
  • 3

6 Answers6

5

I think this is easier:

numToList(NUM,[LIST|[]]):-
   NUM < 10,
   LIST is NUM,
   !.
numToList(NUM,LIST):-
   P is NUM // 10,
   numToList(P,LIST1),
   END is (NUM mod 10), 
   append(LIST1,[END] ,LIST).
false
  • 10,264
  • 13
  • 101
  • 209
user8354592
  • 51
  • 1
  • 1
  • Although I'm a fan of the simplicity of this approach, it should be noted it unfortunately does not work both ways (giving it a list will not build the number), which is something that we should strive for in Prolog, – Gabriel Jablonski Dec 25 '20 at 01:56
4

As already suggested, consider using finite domain constraints:

:- use_module(library(clpfd)).

number_digits(Number, 0, [Number]) :- Number in 0..9.
number_digits(Number, N, [Digit|Digits]) :-
        Digit in 0..9,
        N #= N1 + 1,
        Number #= Digit*10^N + Number1,
        Number1 #>= 0,
        N #> 0,
        number_digits(Number1, N1, Digits).

This predicate can be used in all directions. Examples with either argument instantiated:

?- number_digits(215, _, Ds).
Ds = [2, 1, 5] ;
false.

?- number_digits(N, _, [4,3,2,1]).
N = 4321 ;
false.

And two more general queries:

?- number_digits(N, _, [A,B]).
N in 10..99,
_G2018+B#=N,
_G2018 in 10..90,
A*10#=_G2018,
A in 0..9,
B in 0..9 ;
false.

?- number_digits(N, _, Ds).
Ds = [N],
N in 0..9 ;
Ds = [_G843, _G846],
N in 0..99,
_G870+_G846#=N,
_G870 in 0..90,
_G843*10#=_G870,
_G843 in 0..9,
_G846 in 0..9 ;
etc.
mat
  • 40,498
  • 3
  • 51
  • 78
2

Here comes yet another variant based on ... Based on (#=)/3 and if_//3 we define:

n_base_digits(N, R, Ds) :-
   N #> 0,                                  % positive integers only
   R #> 1,                                  % smallest base = 2
   Ds = [D|_],                              % leading digit may not be 0
   D #> 0,
   phrase(n_base_digits_aux(N, R, Ds), Ds).

n_base_digits_aux(N, Base, [_|Rs]) -->
   { D #= N mod Base,
     M #= N // Base },
   if_(M #= 0,
       { Rs = [] },
       n_base_digits_aux(M, Base, Rs)),
   [D].

Query using SICStus Prolog 4.3.3:

| ?- n_base_digits(1234, 10, Ds).
Ds = [1,2,3,4] ? ;
no

Works the other way round, too!

| ?- n_base_digits(I,10,[1,2,3]).
I = 123 ? ;
no

Note that the above is faster than number_digits/3 as proposed by @mat in his answer.

Community
  • 1
  • 1
repeat
  • 18,496
  • 4
  • 54
  • 166
1

You could also avoid recursion and use in-built predicates for type conversions:

my_digits(Number, List) :-
    atomic_list_concat(List, Atom),
    atom_number(Atom, Number).

The first line converts the list to an atom, and the second line converts this atom to a number, which will give true if that number is the same as that passed in.

I don't know if there is an even more direct way to convert the list into a number (don't think so..), in which case it could be achieved in a single line.

magus
  • 1,347
  • 7
  • 13
0

I don't agree with @ssBarBee. After all, you should get 4321 if you supply your list and their allegation is correct; but instead you get this:

?- my_digits(Num, [1,2,3,4]).
ERROR: is/2: Arguments are not sufficiently instantiated

We could try it with clpfd:

my_digits( 0, [] ).
my_digits(N,[A|As]) :- N1 #= N/10, A #= N mod 10, my_digits(N1, As).

We get this:

?- my_digits(Num, [1,2,3,4]), label([Num]).
Num = -6789 ;
Num = 4321.

I find all that pretty curious, but tracing with clpfd is not pleasant.

If you just wanted to parse a list of numbers I would be inclined to make it tail recursive like so:

my_digits(Num, List) :- my_digits(0, List, Num).

my_digits(Num, [], Num).
my_digits(N, [A|As], Num) :- N1 is N * 10 + A, my_digits(N1, As, Num).

This gives us:

?- my_digits(Num, [1,2,3,4]).
Num = 1234 ;
false.

But it doesn't generate:

?- my_digits(1234, X).
ERROR: is/2: Arguments are not sufficiently instantiated

If I were solving this without clpfd, I'd be inclined at this point to just inspect my arguments and have separate predicates. Gross, I know, but that's what I'd do.

my_digits(Num, List) :- 
    nonvar(List), 
    my_digits_p(0, List, Num).
my_digits(Num, List) :- 
    var(List), 
    my_digits_g(Num, ListRev), 
    reverse(ListRev, List).

my_digits_p(Num, [], Num).
my_digits_p(N, [A|As], Num) :- N1 is N * 10 + A, my_digits(N1, As, Num).

my_digits_g(0, []) :- !.
my_digits_g(N, [A|As]) :- A is N mod 10, N1 is floor(N / 10), my_digits_g(N1, As).

This can parse or check, or generate if the number is a non-variable:

?- my_digits(1234, X).
X = [1, 2, 3, 4].

?- my_digits(X, [1,2,3,4]).
X = 1234 ;
false.

?- my_digits(1234, [1,2,3,4]).
true;
false.

If you try and generate with both arguments as variables you'll get a pretty unhelpful result though:

?- my_digits(X, Y).
X = 0,
Y = [].

So we can try and generate by adding another special case to my_digits:

my_digits(Num, List) :- 
    var(Num), var(List), 
    my_digits_g_from(0, Num, ListRev), 
    reverse(ListRev, List).
my_digits(Num, List) :- 
    nonvar(List), 
    my_digits_p(0, List, Num).
my_digits(Num, List) :- 
    var(List), 
    my_digits_g(Num, ListRev),
    reverse(ListRev, List).

my_digits_g_from(N, N, List)   :- my_digits_g(N, List).
my_digits_g_from(N, Num, List) :- succ(N, N1), my_digits_g_from(N1, Num, List).

That's a lot of code, and a good demonstration of the kind of acrobatics one has to do when not using clp(fd). It's an unfortunate fact that when doing arithmetic in Prolog one must work around the fact that is does not unify, but the complexity of clp(fd) is good proof of why that is.

I hope someone else has a more elegant solution!

Daniel Lyons
  • 22,421
  • 2
  • 50
  • 77
  • I agree Daniel. I rushed with a comment, which lead to an inaccurate one. +1 for the work and time you've invested into the code above. – ssbarbee Apr 17 '13 at 16:33
  • 1
    It happens to us all. Thanks! – Daniel Lyons Apr 17 '13 at 16:44
  • This yields an instantiation error for example on the query `?- my_digits(N, [_]).` – mat Apr 17 '13 at 18:22
  • Yes, it's not perfect. Like I mentioned, this is more of a demonstration of how hard it is to deal with arithmetic outside of `clp(fd)`. If you see an easy way to fix that I'd like to know it. – Daniel Lyons Apr 17 '13 at 19:26
  • 1
    Easy: Check out the clp(fd) version I posted. Why do it with low-level arithmetic if it feels gross even to yourself? You conveyed the impression that your final version is a finished alternative, I only wanted to point out explicitly that despite your efforts (which I admire), it *still* is not. – mat Apr 18 '13 at 07:13
0

For a class assignment? What the professor is probably looking for is something like the following. A a general rule, your analysis of the problem statement should first identify the special cases (in this case, zero and negative values) and then the general case.

: -- int_2_digits/2 ------------------------------------------------------------
: 
: The public api.
:
: we've got 2 special cases here:
: 
: * zero, and
: * negative numbers
:
: and, of course, the general case: a positive value.
:
: ------------------------------------------------------------------------------
int_2_digits( 0 , [0] ) .       : zero is a special case
int_2 digits( X , ['-'|Ds] ) :- : negative numbers are a special case
  X < 0 ,                       :   which we handle (YMMV) by prepending the
  X1 is - X ,                   :   sign and than processing the absolute value
  int_2_digits(X1,Ds) .         :
int_2_digits( X , Ds       ) :- : the general case is a positive value
  X > 0 ,                       : just invoke the worker predicate.
  int_2_digits(X,[],Ds) .       :

: -- int_2_digits/3 ------------------------------------------------------------
: 
: The guts of the operation.
: 
: We're using an accumulator here because we compute the result right-to-left,
: from least significant digit to most significant digit. Using the accumulator
: builds the list in the correst sequence, so we don't have to reverse it at
: the end.
: ------------------------------------------------------------------------------
int_2_digits( 0 , Ds , Ds ) .      : if we hit zero, we're done. Unify the accumulator with the result
int_2_digits( X , Ts  , Ds ) :-    : otherwise...
  D is mod(X,10) ,                 : - get the current digit (X modulo 10)
  T is div(X,10) ,                 : - get the next value via integer division
  int_2_digits( X1 , [T|Ts] , Ds ) : - recurse down
  .                                : Easy!
Nicholas Carey
  • 71,308
  • 16
  • 93
  • 135