RabbitFarm

2020-12-06

Perl Weekly Challenge 089 (Prolog solutions)

Part 1

You are given a positive integer $N. Write a script to sum GCD of all possible unique pairs between 1 and $N.

Solution


range_list(0, [0]).
range_list(N, List):-
    range_list(N, [], List).
range_list(0, List, List).
range_list(N, ListAccum, List):-
    N0 is N - 1,
    range_list(N0, [N|ListAccum], List).

unique_pairs(List, Pairs):-
    unique_pairs(List, List, [], Pairs).

unique_pairs([], [], Pairs, Pairs).
unique_pairs([_|T0], [], PairsAccum, Pairs):-
   unique_pairs(T0, T0, PairsAccum, Pairs).
unique_pairs([H0|T0], [H1|T1], PairsAccum, Pairs):-
   \+ member([H0, H1], PairsAccum),
   \+ member([H1, H0], PairsAccum),
   H0 \= H1,
   unique_pairs([H0|T0], T1, [[H0, H1]|PairsAccum], Pairs).
unique_pairs([H0|T0], [_|T1], PairsAccum, Pairs):-
   unique_pairs([H0|T0], T1, PairsAccum, Pairs).

write_gcd_pairs(Pairs):-
    write_gcd_pairs(Pairs, 0).
write_gcd_pairs([[I,J]|[]], Sum):-
    Sum0 is Sum + gcd(I, J),
    format("gcd(~d, ~d) = ~d ~n", [I, J, Sum0]).
write_gcd_pairs([[I,J]|T], Sum):-
    format("gcd(~d, ~d) + ", [I, J]),
    Sum0 is Sum + gcd(I, J),
    write_gcd_pairs(T, Sum0).

main:-
    range_list(4, L),
    unique_pairs(L, Pairs),
    write_gcd_pairs(Pairs),
    halt. 

Sample Run


$ gprolog
GNU Prolog 1.4.5 (32 bits)
Compiled Dec  3 2020, 00:37:14 with gcc
By Daniel Diaz
Copyright (C) 1999-2020 Daniel Diaz
| ?- ['prolog/ch-1.p'].
compiling /home/adamcrussell/perlweeklychallenge-club/challenge-089/adam-russell/prolog/ch-1.p for byte code...
/home/adamcrussell/perlweeklychallenge-club/challenge-089/adam-russell/prolog/ch-1.p compiled, 36 lines read - 6945 bytes written, 52 ms

(26 ms) yes
| ?- main.
gcd(3, 4) + gcd(2, 4) + gcd(2, 3) + gcd(1, 4) + gcd(1, 3) + gcd(1, 2) = 7 

Notes

This mostly follows the approach of the Perl solution for this problem. The problem is broken down into the following pieces

Part 2

You are given m x n matrix of positive integers. Write a script to print spiral matrix as a list.

Solution


all_unique(_, []).
all_unique(L, [V|T]) :-
    fd_exactly(1, L, V),
    all_unique(L, T).

pwc_matrix(R1,R2,R3) :-
    R1 = [A, B, C],
    R2 = [D, E, F],
    R3 = [G, H, I],
    /* each element is a number from 1 to 9 */  
    fd_domain([A, B, C], 1, 9),
    fd_domain([D, E, F], 1, 9),
    fd_domain([G, H, I], 1, 9),
    /* ensure each element is unique */
    all_unique([A, B, C, D, E, F, G, H, I], [1, 2, 3, 4, 5, 6, 7, 8, 9]),
    /* row constraints */
    A + B + C #= 15,
    D + E + F #= 15,
    G + H + I #= 15,
    /* column constraints */
    A + D + G #= 15,
    B + E + H #= 15,
    C + F + I #= 15,
    /* diagonal constraints */
    A + E + I #= 15,
    C + E + G #= 15,
    /* label all variables to instantiate one solution */  
    fd_labeling([A, B, C, D, E, F, G, H, I]).  

write_rows([]).
write_rows([H|T]):-
    format('[ ~d ~d ~d ]~n', H),
    write_rows(T).

write_solutions([]). 
write_solutions([H|T]):-
   write_rows(H), 
   nl,
   write_solutions(T). 

main :-
    findall([R1,R2,R3], pwc_matrix(R1,R2,R3), Solutions),  
    write_solutions(Solutions). 

Sample Run


$ gprolog
GNU Prolog 1.4.5 (32 bits)
Compiled Dec  3 2020, 00:37:14 with gcc
By Daniel Diaz
Copyright (C) 1999-2020 Daniel Diaz
| ?- ['prolog/ch-2.p'].
compiling /home/adamcrussell/perlweeklychallenge-club/challenge-089/adam-russell/prolog/ch-2.p for byte code...
/home/adamcrussell/perlweeklychallenge-club/challenge-089/adam-russell/prolog/ch-2.p compiled, 42 lines read - 6581 bytes written, 50 ms

(31 ms) yes
| ?- main.
[ 2 7 6 ]
[ 9 5 1 ]
[ 4 3 8 ]

[ 2 9 4 ]
[ 7 5 3 ]
[ 6 1 8 ]

[ 4 3 8 ]
[ 9 5 1 ]
[ 2 7 6 ]

[ 4 9 2 ]
[ 3 5 7 ]
[ 8 1 6 ]

[ 6 1 8 ]
[ 7 5 3 ]
[ 2 9 4 ]

[ 6 7 2 ]
[ 1 5 9 ]
[ 8 3 4 ]

[ 8 1 6 ]
[ 3 5 7 ]
[ 4 9 2 ]

[ 8 3 4 ]
[ 1 5 9 ]
[ 6 7 2 ]


(5 ms) yes

Notes

This is really not too tremendously different than a Sudoku, which just came up a couple of weeks ago. Obviously the constraints are different but the general approach is very similar. Here I am using Gnu Prolog’s finite domain (FD) constraint solver functions. In the past I primarily used SWI-Prolog and for this sort of problem I’d specifically make use of SWI-Prolog’s library(clpfd). Conceptually, the implementations are virtually identical which slightly different predicates. Gnu Prolog seems much faster, but I have neither confirm nor denied that with any sort of benchmarks.

posted at: 20:10 by: Adam Russell | path: /prolog | permanent link to this entry