RabbitFarm

2022-11-20

The Weekly Challenge 191 (Prolog Solutions)

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

Part 1

You are given an encoded string consisting of a sequence $s of numeric characters: 0..9. Write a script to find the all valid different decodings in sorted order.

Solution


twice_greater(X, Y, TwiceGreater):-
    X \== Y,
    TwiceY is 2 * Y,
    X >= TwiceY,
    TwiceGreater = -1.
twice_greater(X, Y, TwiceGreater):-
    TwiceY is 2 * Y,
    X < TwiceY,
    TwiceGreater = 1.

twice_largest(List):-
    max_list(List, Max),
    maplist(twice_greater(Max), List, TwiceGreater),
    delete(TwiceGreater, -1, TwiceGreaterOneDeleted), 
    length(TwiceGreaterOneDeleted, TwiceGreaterOneDeletedLength),
    TwiceGreaterOneDeletedLength == 1, !.

Sample Run


$ gprolog --consult-file prolog/ch-2.p
| ?- twice_largest([1, 2, 3, 4]).

no
| ?- twice_largest([1, 2, 0, 5]).

yes
| ?- twice_largest([2, 6, 3, 1]).

yes
| ?- twice_largest([4, 5, 2, 3]).

no

Notes

There are a few ways one could approach this problem. I thought this implementation was nice and concise, albeit unconventional. maplist/3 is used to generate a list with entries corresponding to whether or not the respective element, times two, in the original List was more or less than the List Max. If we find only one element fails this, the List Max itself, then twice_largest/1 is true.

Part 2

You are given an integer, 0 < $n <= 15. Write a script to find the number of orderings of numbers that form a cute list.

Solution


cute(_, _) --> [].
cute(N, CuteList) --> [X], {between(1, N, X), \+ member(X, CuteList), 
                            length(CuteList, CuteListLength),
                            succ(CuteListLength, I),
                            (0 is mod(X, I); 0 is mod(I, X)),
                            append(CuteList, [X], CuteListUpdated)}, 
                            cute(N, CuteListUpdated).

main:-
    N = 15, 
    findall(Cute, (length(Cute, N), phrase(cute(N, []), Cute)), C), 
    sort(C, CuteList), 
    length(CuteList, NumberCuteList),
    write(NumberCuteList), nl.         

Sample Run


$ gprolog --consult-file prolog/ch-2.p
| ?- main.
24679

Notes

This is a somewhat convoluted use of a DCG and, in turn, the DCG code itself might be a bit convoluted. Here the DCG will generate all lists which conform to the given rules. There ends up being some duplication which is natural given the condition. To remove the duplicates I sort/2 the results.

References

Challenge 191

posted at: 16:05 by: Adam Russell | path: /prolog | permanent link to this entry