RabbitFarm

2022-08-14

The Weekly Challenge 177 (Prolog Solutions)

The examples used here are from the weekly challenge problem statement and demonstrate the working solution.

Part 1

You are given a positive number, $n. Write a script to validate the given number against the included check digit.

Solution


damm_matrix(0, [0, 7, 4, 1, 6, 3, 5, 8, 9, 2]).
damm_matrix(1, [3, 0, 2, 7, 1, 6, 8, 9, 4, 5]).
damm_matrix(2, [1, 9, 0, 5, 2, 7, 6, 4, 3, 8]).
damm_matrix(3, [7, 2, 6, 0, 3, 4, 9, 5, 8, 1]).
damm_matrix(4, [5, 1, 8, 9, 0, 2, 7, 3, 6, 4]).
damm_matrix(5, [9, 5 ,7, 8, 4, 0, 2, 6, 1, 3]).
damm_matrix(6, [8, 4, 1, 3, 5, 9, 0, 2, 7, 6]).
damm_matrix(7, [6, 8, 3, 4, 9, 5, 1, 0, 2, 7]).
damm_matrix(8, [4, 6, 5, 2, 7, 8, 3, 1, 0, 9]).
damm_matrix(9, [2, 3, 9, 6, 8, 1, 4, 7, 5, 0]).

damm_validate(N):-
    number_chars(N, NChars),
    damm_validate(NChars, 0).
damm_validate([], InterimDigit):-
    InterimDigit == 0.    
damm_validate([H|T], InterimDigit):-
    number_chars(N, [H]),
    damm_matrix(N, DammRow),
    succ(InterimDigit, I),
    nth(I, DammRow, NextInterimDigit),
    damm_validate(T, NextInterimDigit). 

Sample Run


| ?- damm_validate(5727).

(1 ms) no
| ?- damm_validate(5724).

yes

Notes

The beauty of Prolog is when it's implicit features such as backtracking and unification are exclusively leveraged to obtain a beautiful solution. This is not one of those cases! This is pure recursion, more functional than logical. I can't think of a more elegant way to express this Damm Validation process, however. Essentially we are performing a series of lookups from a table. I could see this being done with a DCG, perhaps. But in that case we wouldn't really be making anything more elegant, I would argue, just removing the explicit recursion while still having to do the same sort of lookups. It would probably end up being more code than this!

Anyway, Damm Validation is pretty succinctly expressed, it's just that the algorithm doesn't seem to really lend itself to being made much more logically implemented.

Part 2

Write a script to generate first 20 Palindromic Prime Cyclops Numbers.

Solution


cyclops(X):-
    number_chars(X, XChars),
    length(XChars, XCharsLength),
    XCharsLengthMinusOne is XCharsLength - 1,
    delete(XChars, '0', XCharsNoZero),
    length(XCharsNoZero, NoZeroLength),
    NoZeroLength == XCharsLengthMinusOne,
    append(Beginning, ['0'|End], XChars),
    length(Beginning, BeginningLength),
    length(End, EndLength),
    BeginningLength == EndLength.

palindrome(X):-
    number_codes(X, C),
    reverse(C, CR),
    number_codes(X, CR).

palindrome_prime(Prime):-
    current_prolog_flag(max_integer, MAX_INTEGER),
    between(100, MAX_INTEGER, Prime),
    palindrome(Prime),
    fd_prime(Prime).

palindromic_prime_cyclops(_) --> [].
palindromic_prime_cyclops(Seen) --> [X], {palindrome_prime(X), cyclops(X), \+ member(X, Seen)}, palindromic_prime_cyclops([X|Seen]).

main:-
    length(PalindromicPrimeCyclops, 5),
    phrase(palindromic_prime_cyclops([]), PalindromicPrimeCyclops),
    write(PalindromicPrimeCyclops), nl.

Sample Run


$ gprolog --consult-file prolog/ch-2.p 
| ?- length(PalindromicPrimeCyclops, 20), phrase(palindromic_prime_cyclops([]), PalindromicPrimeCyclops).

PalindromicPrimeCyclops = [101,16061,31013,35053,38083,73037,74047,91019,94049,1120211,1150511,1160611,1180811,1190911,1250521,1280821,1360631,1390931,1490941,1520251] ? 

Notes

This borrows a quite a bit of code from previous challenges! Probably the newest thing here is the checking of the cyclops condition. In cyclops/1 we first check to see if there is a single zero. This is done by removing all zeroes with delete/3 and then confirming, by checking lengths, that only one was removed. After that we split the list around the '0' using append/3 and if the sublists before and after the '0' are of the same size we know we have a cyclops number. Notice that it only matters that they are equal. Whether they are of even length or odd length doesn't matter since we know we have just a single '0' and so the length of the entire list is necessarily of odd length, as required.

References

Challenge 177

posted at: 17:37 by: Adam Russell | path: /prolog | permanent link to this entry