RabbitFarm

2025-06-22

The Weekly Challenge 326 (Prolog Solutions)

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

Part 1: Day of the Year

You are given a date in the format YYYY-MM-DD. Write a script to find day number of the year that the given date represent.

Our solution is short, it involves just a couple of computations, and will be contained in a single file that has the following structure.

"ch-1.p" 1


day month year 4
leap year 2
february days 3
day of the year 5

We’ll put the determination of whether a year is a leap year or not into its own predicate.

leap year 2 ⟩≡


leap_year(Year):-
M1 is Year mod 4,
M2 is Year mod 100,
M3 is Year mod 400,
((M1 == 0, \+ M2 == 0);
(M1 == 0, M2 == 0, M3 == 0)).

Fragment referenced in 1.

Similarly, we’ll put the calculation of the number of February days in its own predicate.

february days 3 ⟩≡


february_days(Year, Days):-
leap_year(Year),
Days = 29.
february_days(_, Days):-
Days = 28.

Fragment referenced in 1.

One more utility predicate, which splits the input into day, month, and year values.

day month year 4 ⟩≡


day_month_year(S, Day, Month, Year):-
append(Y, [45|T], S),
append(M, [45|D], T),
number_codes(Day, D),
number_codes(Month, M),
number_codes(Year, Y).

Fragment referenced in 1.

Finally, let’s compute the day of the year.

day of the year 5 ⟩≡


day_of_year(Date, DayOfYear) :-
day_month_year(Date, Day, Month, Year),
february_days(Year, FebruaryDays),
DaysInMonth = [31, FebruaryDays, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31],
succ(M, Month),
length(Prefix, M),
prefix(Prefix, DaysInMonth),
sum_list(Prefix, MonthSum),
DayOfYear is MonthSum + Day.

Fragment referenced in 1.

Sample Run
$ gprolog --consult-file prolog/ch-1.p 
| ?- day_of_year("2025-02-02", DayOfYear). 
 
DayOfYear = 33 ? 
 
yes 
| ?- day_of_year("2025-04-10", DayOfYear). 
 
DayOfYear = 100 ? 
 
yes 
| ?- day_of_year("2025-09-07", DayOfYear). 
 
DayOfYear = 250 ? 
 
yes 
| ?-
    

Part 2: Decompressed List

You are given an array of positive integers having even elements. Write a script to to return the decompress list. To decompress, pick adjacent pair (i, j) and replace it with j, i times.

The code required is fairly small, we’ll just need a couple of predicates.

"ch-2.p" 6


state of the decompression 7
decompress 8
decompress list 9

We’ll define a DCG to “decompress”the list. First, let’s have some predicates for maintaining the state of the decompression as it proceeds.

state of the decompression 7 ⟩≡


decompression(Decompression), [Decompression] --> [Decompression].
decompression(D, Decompression), [Decompression] --> [D].

Fragment referenced in 6.

The DCG for this is not so complex. Mainly we need to be concerned with maintaining the state of the decompression as we process the list.

decompress 8 ⟩≡


decompress(Input) --> decompression(D, Decompression),
{Input = [I, J|T],
length(L, I),
maplist(=(J), L),
append(D, L, Decompression)
},
decompress(T).
decompress([]) --> [].

Fragment referenced in 6.

Finally, let’s wrap the calls to the DCG in a small predicate using phrase/3.

decompress list 9 ⟩≡


decompress_list(L, Decompressed):-
phrase(decompress(L), [[]], [Decompressed]).

Fragment referenced in 6.

Sample Run
$ gprolog --consult-file prolog/ch-2.p 
| ?- decompress_list([1, 3, 2, 4], Decompressed). 
 
Decompressed = [3,4,4] 
 
yes 
| ?- decompress_list([1, 1, 2, 2], Decompressed). 
 
Decompressed = [1,2,2] 
 
yes 
| ?- decompress_list([3, 1, 3, 2], Decompressed). 
 
Decompressed = [1,1,1,2,2,2] 
 
yes 
| ?-
    

References

The Weekly Challenge 326
Generated Code

posted at: 18:45 by: Adam Russell | path: /prolog | permanent link to this entry