RabbitFarm

2022-11-06

The Weekly Challenge 189 (Prolog Solutions)

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

Part 1

You are given an array of characters (a..z) and a target character. Write a script to find out the smallest character in the given array lexicographically greater than the target character.

Solution


greater_than_character(Target, C0, C1):-
    C0 > Target,
    C1 = C0.   
greater_than_character(Target, C0, C1):-
    \+ C0 > Target,
    C1 = nil.  

greater_character(Characters, Target, Greater):-
    maplist(greater_than_character(Target), Characters, GreaterCharacters),
    delete(GreaterCharacters, nil, GreaterCharactersNonNil),
    length(GreaterCharactersNonNil, GreaterCharactersNonNilLength),
    GreaterCharactersNonNilLength > 0,
    min_list(GreaterCharactersNonNil, GreaterChar),
    char_code(Greater, GreaterChar), !.    
greater_character(Characters, [Target], Greater):-
    maplist(greater_than_character(Target), Characters, GreaterCharacters),
    delete(GreaterCharacters, nil, GreaterCharactersNonNil),
    length(GreaterCharactersNonNil, GreaterCharactersNonNilLength),
    GreaterCharactersNonNilLength == 0,
    char_code(Greater, Target), !.    

Sample Run


$ gprolog --consult-file prolog/ch-1.p
| ?- greater_character("emug", "b", LeastGreaterCharacter).

LeastGreaterCharacter = e

(1 ms) yes
| ?- greater_character("dcef", "a", LeastGreaterCharacter).

LeastGreaterCharacter = c

yes
| ?- greater_character("jar", "o", LeastGreaterCharacter). 

LeastGreaterCharacter = r

(1 ms) yes
| ?- greater_character("dcaf", "a", LeastGreaterCharacter).

LeastGreaterCharacter = c

(1 ms) yes
| ?- greater_character("tgal", "v", LeastGreaterCharacter).

LeastGreaterCharacter = v

yes

Notes

First off, I should note that the use of double quoted strings here might confuse some people. To clarify, in GNU Prolog what look like double quoted strings are handled as lists of character codes. Character codes, not characters! So the use of Character in some variable names may seem a little distracting. They are accurate in intent, but if you are unaware of what's going on it may seem a little strange.

For the solution itself I use a trick with maplist/3 that I have used previously. greater_than_character/3 will either return the character greater than the target or nil otherwise. min_list/2 is then used to get the smallest character which is greater than the target, as required. Also, note that in the case no character is found to be greater than the target we instead supply the target itself.

Part 2

You are given an array of 2 or more non-negative integers. Write a script to find out the smallest slice, i.e. contiguous subarray of the original array, having the degree of the given array.

Solution


array_degree(Array, Degree):-
    array_degree(Array, Array, 0, Degree), !.
array_degree([], _, Degree, Degree).    
array_degree([H|T], Array, DegreeAccum, Degree):-
    length(Array, ArrayLength),
    delete(Array, H, ArrayWithout),    
    length(ArrayWithout,ArrayWithoutLength),
    CurrentDegree is ArrayLength - ArrayWithoutLength,
    CurrentDegree > DegreeAccum,
    array_degree(T, Array, CurrentDegree, Degree).
array_degree([H|T], Array, DegreeAccum, Degree):-
    length(Array, ArrayLength),
    delete(Array, H, ArrayWithout),    
    length(ArrayWithout,ArrayWithoutLength),
    CurrentDegree is ArrayLength - ArrayWithoutLength,
    \+ CurrentDegree > DegreeAccum,
    array_degree(T, Array, DegreeAccum, Degree).    

least_slice_degree(Array, LeastDegreeSlice):-
    array_degree(Array, ArrayDegree),
    findall(Sublist, (prefix(Prefix, Array), suffix(Suffix, Array), 
                      sublist(Sublist, Array), length(Sublist, SublistLength), 
                      SublistLength >= 2, flatten([Prefix, Sublist, Suffix], Array)), Sublists),
    sort(Sublists, Slices),                  
    findall(DegreeSlice, (member(Slice, Slices), array_degree(Slice, Degree), DegreeSlice = Degree-Slice), DegreeSlices),
    findall(MatchingSlice, (member(DegreeSlice, DegreeSlices), ArrayDegree-MatchingSlice = DegreeSlice), MatchingSlices),
    findall(LengthSlice, (member(MatchingDegreeSlice, MatchingSlices), length(MatchingDegreeSlice, MatchingDegreeSliceLength), LengthSlice = MatchingDegreeSliceLength-MatchingDegreeSlice), LengthSlices),
    keysort(LengthSlices),
    [_-LeastDegreeSlice|_] = LengthSlices. 

Sample Run


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

LeastDegreeSlice = [3,3]

(6 ms) yes
| ?- least_slice_degree([1, 2, 1, 3], LeastDegreeSlice). 

LeastDegreeSlice = [1,2,1]

(6 ms) yes
| ?- least_slice_degree([1, 3, 2, 1, 2], LeastDegreeSlice). 

LeastDegreeSlice = [2,1,2]

(19 ms) yes
| ?- least_slice_degree([1, 1, 2, 3, 2], LeastDegreeSlice). 

LeastDegreeSlice = [1,1]

(19 ms) yes
| ?- least_slice_degree([2, 1, 2, 1, 1], LeastDegreeSlice).       

LeastDegreeSlice = [1,2,1,1]

(20 ms) yes

Notes

This is the most I've used findall/3 in a long time! The main complexity here, I feel, is in that we must compute all contiguous slices of the original list. sublist/2 is not useful by itself here as it returns sublists which are not contiguous, only ordered. With the help of prefix/2 and suffix/2 we are able to identify contiguous sublists.

findall/3 is used, then, to obtain and then process all of these contiguous slices to ultimately identify the one that meets all criteria. First we identify all slices, then we obtain all degree/slice pairs, and then finally we examine the lengths.

References

Challenge 189

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