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
Use clpfd!
:- 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 clpfd 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)
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.