2

I need to make a predicate that receives a numeric list and print only the numbers that end in 7 and that the sum of its digits is greater than 100

I made the predicates for separated but I need help making a union of the two predicates, I mean that the two predicates go into one only predicate, this is what I did so far:

%sum of digits greater than 100
 multi(X):-
0 is X mod 100
sum([],0).
sum([P|Q],Z).
multi(P), sum(Q,Z1), Z is P + Z1.
sum([P|Q],Z).
not multi(P), sum(Q,Z).

%print the numbers that end in 7
end(Y):-
7 is Y mod 10.
listend([],0).
listend([P|Q]):-
end(P),write(P), nl, listend(Q).
listend([P|Q]):-
not(end(P)), listend(Q).
repeat
  • 18,496
  • 4
  • 54
  • 166

2 Answers2

4

Use !

:- use_module(library(clpfd)).

We do it like this:

n_base10(N, Ds) :-
   n_base_digits(N, 10, Ds).

n_base_digits(Expr, Base, Ds) :-
   Base #> 1,
   Ds = [_|_],
   N #=  Expr,
   N #>= 0,                                   % N is non-negative
   n_base_ref_acc_digits(N, Base, Ds, [], Ds).

n_base_ref_acc_digits(N, Base, Ref, Ds0, Ds) :-
   zcompare(Order, N, Base),
   order_n_base_ref_acc_digits(Order, N, Base, Ref, Ds0, Ds).

order_n_base_ref_acc_digits(<, N,    _, [_]   , Ds0,   [N|Ds0]).
order_n_base_ref_acc_digits(=, _,    _, [_,_] , Ds0, [1,0|Ds0]).
order_n_base_ref_acc_digits(>, N, Base, [_|Rs], Ds0, Ds) :-
   N0 #= N //  Base,
   N1 #= N mod Base,
   n_base_ref_acc_digits(N0, Base, Rs, [N1|Ds0], Ds).

Some simple queries1:

?- n_base10(_, []).
false.

?- X #< 0, n_base10(X, Ds).
false.

?- n_base10(123, [1,2,3]).
true.                                   

?- n_base10(123, Ds).
Ds = [1,2,3].

?- n_base10(N, [1,7,9]).
  N = 179
; false.

?- n_base10(459183754813957135135239458256, Ds).
Ds = [4,5,9,1,8,3,7,5,4,8,1,3,9,5,7,1,3,5,1,3,5,2,3,9,4,5,8,2,5,6].

How about using bases other than 10?

?- member(Base,[2,8,10,16,36]), n_base_digits(N,Base,[1,2,3,4]).
  Base =  8, N =   668
; Base = 10, N =  1234
; Base = 16, N =  4660
; Base = 36, N = 49360
; false.

?- member(Base,[2,8,10,16,36]), n_base_digits(101,Base,Ds).
  Base =  2, Ds = [1,1,0,0,1,0,1]
; Base =  8, Ds =         [1,4,5]
; Base = 10, Ds =         [1,0,1]
; Base = 16, Ds =           [6,5]
; Base = 36, Ds =           [2,29].

OK! Works as expected.

Let's find integers with digit sum greater than 100 and 7 as the least significant decimal digit!

?- set_prolog_flag(toplevel_print_anon, false).
true.

?- _S #> 100,
   n_base10(N, _Ds),
   lists:last(_Ds, 7),
   clpfd:sum(_Ds, #=, _S),
   clpfd:labeling([ff,min(N)], _Ds).
  N = 499999999997
; N = 589999999997
; N = 598999999997 
...

Now, on to the "filtering" part of your question... it's as easy as 1, 2, 3.

First, we define (@)/2 based on (@)/1 . It fits the reification scheme (of if_/3, (=)/3, etc.) which already has been used in a lot of logically-pure Prolog answers on StackOverflow.

@(G_0, T) :- @var(T), @G_0, T = true.

Second, we define reified versions of the predicates (#=)/2 and (#>)/2.

#=(X, Y, T) :- X #= Y #<==> B, bool01_t(B, T).

#>(X, Y, T) :- X #> Y #<==> B, bool01_t(B, T).

Last, using Prolog lambdas, tfilter/3 and ','/3, we inquire:

?- use_module(library(lambda)).
true.

?- Zs0 = [                              /* Es: list of sample integers */
             499999999997,              /*     (digit sum = 101)       */
            9899999999970,              /*     (digit sum = 105)       */
          516666669999997,              /*     (digit sum = 103)       */
                  5000007,              /*     (digit sum =  12)       */
             598999999997               /*     (digit sum = 101)       */
         ],
   tfilter(\N^(                         /* N:  candidate integer       */
               @n_base10(N, Ds),        /* Ds: base-10 representation  */
               @lists:last(Ds, D1),     /* D1: least significant digit */
               D1 #= 7,                 /* D1:              equal to 7 */
               @clpfd:sum(Ds, #=, S),   /* S:  digit sum               */
               S #> 100                 /* S:         greater than 100 */
              ),
           Zs0,
           Zs).
Zs0 = [499999999997,9899999999970,516666669999997,5000007,598999999997],
Zs  = [499999999997,              516666669999997,        598999999997].

Works like a charm!


Footnote 1: Using SWI-Prolog version 7.3.10 (64-bit AMD64)

Community
  • 1
  • 1
repeat
  • 18,496
  • 4
  • 54
  • 166
  • `n_base_digits/3` seems really good but is it extensible to negative numbers too? – Fatalize Jul 09 '16 at 18:30
  • @Fatalize. Sure it can be used for that, too. Best handle the sign upfront! That way, you can use above code as-is. – repeat Jul 20 '16 at 12:29
2

This works for me:

?- filter([147, 24, 57, 17, 3667], X), write(X), nl, fail.

sumdigits(0, 0).
sumdigits(X, Z) :-
    X > 0,
    Z1 is X mod 10, 
    X2 is X // 10,
    sumdigits(X2, Z2), 
    Z is Z1 + Z2.

filter([], []).
filter([H|X], [H|Y]) :-
    sumdigits(H, D),
    D > 10,
    7 is H mod 10, !,
    filter(X, Y).
filter([_|X], Y) :- filter(X, Y).

I get:

[147, 57, 3667]
No.

I assumed you meant that the sum of the digits was greater than 10, rather than 100.

Enigmativity
  • 113,464
  • 11
  • 89
  • 172
  • 1
    Thanks! but no still the sum of the digits has to be greater than 100 – Brian Daniel García Nov 05 '15 at 02:55
  • @BrianDanielGarcía - Then you have a problem. To get a number with the sum of the digits greater than `100` and have it end in `7` then the smallest such number is `9 999 999 997` and that isn't a valid integer so the code returns no results. – Enigmativity Nov 05 '15 at 03:09
  • 1
    @Enigmativity. The digit sum of the integer number `9_999_999_997` is **not** greater than `100`, it is smaller! The goal `9+9+9+9+9+9+9+9+9+7 =:= 88` succeeds... – repeat Nov 05 '15 at 10:46
  • @repeat - Sorry, you're right. But the same problem still exists. – Enigmativity Nov 05 '15 at 10:48
  • @Enigmativity. Take it easy! Which problem are you referring to? – repeat Nov 05 '15 at 11:16
  • 1
    @repeat - What did I say that made you say, "Take it easy!"?? The problem is that a number with enough digits to have a sum of digits over 100 can't be represented as an integer - it's too large. So `9 999 999 997` and `999 999 999 997` have the same representation problem. – Enigmativity Nov 05 '15 at 23:06
  • No offense... Your statement about that particular integer being too big (and thus invalid) is not true in general; it depends on the Prolog implementation. Many modern Prolog processors (both free and proprietary) support arbitrary-precision integer arithmetics. So, what I meant to say was "no problemo, simply switch the Prolog processor and you're good to go". Chances are that the teacher of that particular novice chose "100 digits" on purpose, because most Prolog processors deal with numbers of that size effortlessly. Could you show the error/warning you get with `?- X is 7^7^7.` Thx! – repeat Nov 06 '15 at 07:15
  • @repeat - `Warning 4: The string ^ is not an operator. (line 1, before the first clause)` – Enigmativity Nov 06 '15 at 08:56
  • @repeat - If I do `?- X is 9999999999, write(X).` I get `1410065407Yes.` If I do `?- X is 999999999, write(X).` I correctly get `999999999Yes.`. – Enigmativity Nov 06 '15 at 08:58
  • Getting wrong results without warning/error/exception *is* bad. Why not simply switch the Prolog processor? – repeat Nov 06 '15 at 11:53
  • Let us [continue this discussion in chat](http://chat.stackoverflow.com/rooms/94432/discussion-between-enigmativity-and-repeat). – Enigmativity Nov 06 '15 at 13:23