Iterate checking a list

query tested:

?-generate_number(1,10).

After last iteration of generate number the function number_digits pass [1,0] to check ( the number 10) and check returns fail and the program quit without checking the other numbers.

The problem to solve is:
"A lucky number is a 10-based number, which has at least a “6” or an “8” in its digits. However, if it has “6” and “8” at the same time, then the number is NOT lucky. For example, “16”, “38”, “666” are lucky numbers, while “234” , “687” are not.

Now we want to know how many lucky numbers (without leading zeroes) are there between LB and UB, inclusive? "


generate_number(UB,UB):-!

generate_number(LB,UB):-
    LB =< UB,  
    LB1 is LB+1,
    generate_number(LB1,UB),
    
    number_digits(LB1,_,L),
	check(L, V), 
   
	%V==true-> append(LB,LU,LU).
    
check([T], false).


check([H|T], V):-
    check(T,V),
    V \= true,
    H == 6,
    V = true;
    check(T,V),
    V\=true,
    H == 8,
    V = true.

:- 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).

Some hints, based on what I understood.

You don’t seem to need library(clpfd) for what you are doing?

For generating integers in between “lower” and “upper”, use between/3.

Use number_chars/2 to make a list of one-character atoms from a number.

?- number_chars(236, Cs).
Cs = ['2', '3', '6'].

You could use memberchk/2 (or member/2?) to then see if this list has a particular digit in it, like:

?- number_chars(236, Cs), memberchk('6', Cs).
Cs = ['2', '3', '6'].

?- number_chars(236, Cs), memberchk('8', Cs).
false.

For counting solutions, there is the very useful library(aggregate). For example (not useful to you maybe, just for demonstration):

?- aggregate_all(count, ( number_chars(666, Cs), member('6', Cs) ), N).
N = 3. % three sixes in 666

About the exclusive OR, not sure how to do it cleanly. There is an arithmetic function xor() that could be used, if you made a 0 or a 1 out of the answer to the question “does that list contain 6” and “does that list contain 8”.

1 Like

I wonder if aggregate_all could also be used to count how many numbers have a property between two bounds; instead of, say a recursive “loop” with an accumulator argument to count how many numbers in between have the property or not.

Dan

Difficult to say based solely on your question. I have a solution for OP’s question that I don’t want to give in full since this sounds like homework and it will “kill” their submission. But if you could somehow make a 0 or a 1 out of the question “does that number have this property” you could just sum the ones. For example, to count odd numbers (silly example for the sake of the example):

?- aggregate_all(sum(Rem), ( between(1, 10, X), Rem is X rem 2 ), Odd_count).
Odd_count = 5.

I think what is perhaps hard to grasp for those coming from an imperative language is that Prolog is not about doing solution steps (algorithmic thinking), but about describing what is true (via predicates) and letting Prolog do the “looping”.

I guess what it means is that you want to work from ground up – identify the most simple predicate like statement one can make that establishes a truth, and then build up from that.

Dan

Thanks for yours answers.
The program detect 6 and 8 but doesn’t count it.
I made this solution, but the counter doesn’t work properly.

:- use_module(library(clpfd)).
:- use_module(library(aggregate)).
%============================================================================

xor(A,B):-(not(B),A);(not(A),B).

check_member(L,C1,C2):-
    xor(member(C1,L),member(C2,L)).

generate_number(UB,UB,C):-!.

generate_number(LB,UB,C):-
    LB =< UB,
    LB1 is LB+1,
    generate_number(LB1,UB,C1),
    write(C1),
    number_digits(LB1,_,L),
    check_member(L,8,6)->C1 is C+1;!.
	
	
% convert the number in list of digits
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).

You are spending many lines of code on reimplementing existing functionality in a questionable manner. This obfuscates the real problem you might be facing.

I think that the dichotomy between “imperative languages” and Prolog has been long ago blown out of proportion (by well meaning people I am sure) and by now feeds itself in a sinister fashion. It doesn’t seem to die off. I don’t think it really helps.

If we want to move on we need to stop regurgitating the old wisdoms and start asking new questions, hoping to eventually start finding useful answers. :wink:

error#1242-asd

You are now not using any of the two libraries; drop the imports.

Get rid of the cuts, see how it goes.

Debug.

Don’t know – this is what I feel is happening – perhaps there is less of a dichotomy than i think there is

Edit:

Let me try to “deconstruct” declarative and imperative thinking here:

Imperative thinking:

  1. Clearly, we need to test all numbers from a lower bound to an upper bound, hence we need to set up a loop:

  2. we then need to test each number from a low bound to high high bound, if it includes a 6 or an 8 in its digits, but not both

  3. to test a number we need to deconstruct the number into its digits – one way to do it is to recognize that numbers in base 10 are additions of multipliers of the digits x 10 raised to a power and loop though all numbers to identify those adding up to a given number.

Declarative thinking:

  1. Lets do this bottom up and ask what is true:

  2. a (integer) number a list of the integers number’s characters representing that number is true (this truth is given by the number_chars/2 relation.

  3. a list of characters is true when it contains a 6 (is one predicate)

  4. a list of characters is true when it contains an 8
    5 a list of characters is true when it contains a 6 or an 8, but not both

I think “sequential logic” is a bit harder to look at in terms of truth, but, in essence its a true relationship between a current value and a next value, for example:

  1. a next count of lucky numbers is one more of the current count, if the current number is a lucky one
  2. a next count of a lucky number is the same as the current count if the current number is not a lucky number

And finally, there must be some “sequential” relationship that stands on its own and concludes a definition / recursion .

  1. a count of a lucky number is the current count, when a lower bound is higher than an upper bounds

So, the above is an attempt to look at the problem declarative – to break it down into parts that all represent true relations between things - rather than thinking in terms of what steps to perform to achieve a result.

Clearly, there is also the procedural reading included but both readings the declarative and procedural should (ideally) co-exist.

I haven’t tried to translate this into prolog – so i might be missing all kinds of things … but, i guess, this is how i would try to think this through …

Dan

Sorry, but i am trying everything, can you give a check?

this cannot be correct, for example. You probably need to write:

(   check_lucky(...)
->  C1 is C + 1
;   C1 = C
)

You also probably need to delay this until after the recursive call, the way you have now implemented it.

If you used between/3 instead, you could have written something like:

aggregate_all(count, ( between(LB, UB, X), check_lucky(X, ...) ), Count)

But what is the closed form solution for arbitrary upper and lower (not just “all positive integers with up to n digits”)?

1 Like

Here’s my solution - it’s not pretty, but it is fast.

% lucky_list(1, 100, L).
lucky_list(IntLower, IntUpper, Lst) :-
	digits_list(IntLower, LstLower),
	digits_list(IntUpper, LstUpper),
	IntUpper >= IntLower,
	digit_want_avoid(DigitWant, DigitAvoid),
	lucky_list_(LstLower, LstUpper, DigitWant, DigitAvoid, Lst).


% Check of lower
lucky_list_(Lst, _LstUpper, DigitWant, DigitAvoid, Lst) :-
	lucky_list_first(Lst, DigitWant, DigitAvoid, Lst).

lucky_list_(LstLower, LstUpper, DigitWant, DigitAvoid, Lst) :-
	length(LstUpper, LenUpper),
	lucky_list_inc_(LstLower, LstUpper, LenUpper, DigitWant, DigitAvoid, Lst).


lucky_list_first(Lst, DigitWant, DigitAvoid, Lst) :-
	memberchk(DigitWant, Lst),
	maplist(digit_without(DigitAvoid), Lst).


lucky_list_inc_(LstLower, LstUpper, LenUpper, DigitWant, DigitAvoid, Lst) :-
	digit_list_inc(LstLower, DigitWant, DigitAvoid, LstInc),	
	digit_list_not_higher(LstInc, LstUpper, LenUpper),
	(	Lst = LstInc
	;	lucky_list_inc_(LstInc, LstUpper, LenUpper, DigitWant, DigitAvoid, Lst)
	).


update_have_want(true, _, _, true).
update_have_want(false, DigitWant, DigitNext, HaveWant) :-
	(DigitWant = DigitNext -> HaveWant = true ; HaveWant = false).


digit_without(Without, Digit) :-
	between(0, 9, Digit),
	Digit \= Without.


digit_want_avoid(6, 8).
digit_want_avoid(8, 6).


digits_list(Int, Lst) :-
	atom_chars(Int, [H|T]),
	% An integer does not start with zero
	dif(H, 0),
	chars_to_digits_(T, H, Lst).


chars_to_digits_([], H, [Digit]) :-
	atom_number(H, Digit),
	between(0, 9, Digit).

chars_to_digits_([H2|T], H, [Digit|Digits]) :-
	atom_number(H, Digit),
	between(0, 9, Digit),
	chars_to_digits_(T, H2, Digits).


digit_list_not_higher(LstLower, LstUpper, LenUpper) :-
	length(LstLower, LenLower),
	(	LenLower < LenUpper -> true
	;	digit_list_not_higher_same_len_(LstLower, LstUpper)
	).


digit_list_not_higher_same_len_([], []).
digit_list_not_higher_same_len_([HeadLower|_TailLower], [HeadUpper|_TailUpper]) :-
	HeadLower < HeadUpper, !.

digit_list_not_higher_same_len_([HeadLower|TailLower], [HeadUpper|TailUpper]) :-
	HeadLower = HeadUpper,
	digit_list_not_higher_same_len_(TailLower, TailUpper).


digit_list_inc(Lst, DigitWant, DigitAvoid, LstUpdated) :-
    % If any of the digits are > 9, percolate the increments to be =< 9
    digit_list_inc_(Lst, DigitWant, DigitAvoid, false, false, LstUpdated),
	% The first answer is the correct one
	LstUpdated \= Lst, !.

digit_list_inc(Lst, DigitWant, _DigitAvoid, LstUpdated) :-
	% Increase the number of digits
	length(Lst, LstLen),
	succ(ZerosLen, LstLen),
    length(Zeros, ZerosLen),
    maplist(=(0), Zeros),
    append([[1], Zeros, [DigitWant]], LstUpdated).


digit_list_inc_([], _, _, true, _, []).

digit_list_inc_([H], _DigitWant, DigitAvoid, true, false, [HAvoided]) :-
    % Increment the final digit
	inc_avoid(H, DigitAvoid, HAvoided).

% Is a subtle dance between carrying, incrementing, and when to skip ahead
digit_list_inc_([H], DigitWant, _DigitAvoid, false, false, [DigitWant]) :-
	H < DigitWant.

digit_list_inc_([_H], DigitWant, _DigitAvoid, false, true, [DigitWant]).

digit_list_inc_([H], _DigitWant, DigitAvoid, true, true, [HAvoided]) :-
    % Do not increment the final digit, because a carry has been performed
	avoid_check(H, DigitAvoid, HAvoided).

% Ensuring that H is not the last element
digit_list_inc_([H,H2|T], DigitWant, DigitAvoid, HaveWant, false, [HAvoided|Lst]) :-
	avoid_check(H, DigitAvoid, HAvoided),
	update_have_want(HaveWant, DigitWant, HAvoided, HaveWant1),
    digit_list_inc_([H2|T], DigitWant, DigitAvoid, HaveWant1, false, Lst).

digit_list_inc_([H,H2|T], DigitWant, DigitAvoid, HaveWant, _PrevInc, [HAvoided|Lst]) :-
	% Perform a carry
	inc_avoid(H, DigitAvoid, HAvoided),
	update_have_want(HaveWant, DigitWant, HAvoided, HaveWant1),
	% If HN2 is the last digit, reset it, to cater for skips
    (T = [] -> HN2 = 0 ; HN2 is H2 - 10),
    digit_list_inc_([HN2|T], DigitWant, DigitAvoid, HaveWant1, true, Lst).


inc_avoid(Digit, DigitAvoid, DigitIncAvoid) :-
	DigitInc is Digit + 1,
	avoid_check(DigitInc, DigitAvoid, DigitIncAvoid).

avoid_check(Digit, DigitAvoid, DigitIncAvoid) :-
	(Digit = DigitAvoid -> DigitIncAvoid is Digit + 1 ; DigitIncAvoid = Digit),
	between(0, 9, DigitIncAvoid).

Result in swi-prolog 8.5.7:

?- time((findall(L, lucky_list(1, 10000, L), Ls), length(Ls, LsLen))).
% 129,741 inferences, 0.025 CPU in 0.025 seconds (101% CPU, 5228243 Lips)
Ls = [[6],[1,6],[2,6],[3,6],[4,6],[5,6],[6,0],[6,1],[6,2],[6,3],[6,4],[6,5],[6,6],[6,7],[6,9],[7,6],[9,6],[1,0,6],[1,1,6],[1,2,6],[1,3,6],[1,4,6],[1,5,6],[1,6,0],[1,6,1],[1,6,2],[1,6,3],[1,6,4],[1,6,5],[1,6,6],[1,6,7],[1,6,9],[1,7,6],[1,9,6],[2,0,6],[2,1,6],[2,2,6],[2,3,6],[2,4,6],[2,5,6],[2,6,0],[2,6,1],[2,6,2],[2,6,3],[2,6,4],[2,6,5],[2,6,6],[2,6,7],[2,6,9],[2,7,6],[2,9,6],[3,0,6],[3,1,6],[3,2,6],[3,3,6],[3,4,6],[3,5,6],[3,6,0],[3,6,1],[3,6,2],[3,6,3],[3,6,4],[3,6,5],[3,6,6],[3,6,7],[3,6,9],[3,7,6],[3,9,6],[4,0,6],[4,1,6],[4,2,6],[4,3,6],[4,4,6],[4,5,6],[4,6,0],[4,6,1],[4,6,2],[4,6,3],[4,6,4],[4,6,5],[4,6,6],[4,6,7],[4,6,9],[4,7,6],[4,9,6],[5,0,6],[5,1,6],[5,2,6],[5,3,6],[5,4,6],[5,5,6],[5,6,0],[5,6,1],[5,6,2],[5,6,3],[5,6,4],[5,6|...],[5|...],[...|...]|...],
LsLen = 4930.

@brebs
How could any instructor resist giving 10/10 for such an inspired solution!

Here is a more elegant way of incrementing digits in a list, based on prolog - Turn List into number, increment the number, and then turn the number into a list - Stack Overflow

successor([X|Xs], L) :-
	% C is carry digit
	successor(Xs, X, C, Ys),
	% Determine whether to add a final digit for e.g. 999 to 1000
	(	C = 0 -> L = Ys
	;	between(1, 9, C) ->  L = [C|Ys] ).

% Final digit
successor([], X, C, [Y]) :-
	X1 is X + 1,
	divmod(X1, 10, C, Y).

successor([X1|Xs], X, C, [Y|Ys]) :-
	successor(Xs, X1, C0, Ys),
	XC0 is X + C0,
	divmod(XC0, 10, C, Y).

Result:

?- successor([1,2,3], L).
L = [1,2,4].

?- successor([3,7,9], L).
L = [3,8,0].

?- successor([9,9,9], L).
L = [1,0,0,0].