RabbitFarm

2021-08-22

The Weekly Challenge 126 (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 integer $N. Write a script to print count of numbers from 1 to $N that don’t contain digit 1.

Solution


:-initialization(main).

has_1(N):-
    number_codes(N, Codes),
    memberchk(49, Codes).  

count_numbers_without_1(N, Count):-
    count_numbers_without_1(N, 0, Count).  
count_numbers_without_1(1, Count, Count).  
count_numbers_without_1(N, CountAccum, Count):-
    \+ has_1(N),
    succ(CountAccum, C),
    N0 is N - 1,
    count_numbers_without_1(N0, C, Count).  
count_numbers_without_1(N, CountAccum, Count):-
    has_1(N),
    N0 is N - 1,
    count_numbers_without_1(N0, CountAccum, Count).  

main:-
    count_numbers_without_1(15, Count0),
    write(Count0), nl,
    count_numbers_without_1(25, Count1),
    write(Count1), nl,
    halt.   

Sample Run


$ gplc prolog/ch-1.p 
$ prolog/ch-1   
8
13

Notes

The count_numbers_without_1 predicates recurse over the range of numbers and tally the qualifying numbers at each step. has_1/1 converts the numeral to the list of associated ascii codes and then we see if the ascii code for '1' (49) is present.

Part 2

You are given a rectangle with points marked with either x or *. Please consider the x as a land mine. Write a script to print a rectangle with numbers and x as in the Minesweeper game.

Solution


:-initialization(main).

rows(5).
columns(10).
grid([x, '*', '*', '*', x, '*', x, x, x, x, 
      '*', '*', '*', '*', '*', '*', '*', '*', '*', x,  
      '*', '*', '*', '*', x, '*', x, '*', x, '*',   
      '*', '*', '*', x, x, '*', '*', '*', '*', '*',
       x, '*', '*', '*', x, '*', '*', '*', '*', x]).

write_grid([H|T]):-
    write('\t'),
    write_grid([H|T], 0).
write_grid([], _).    
write_grid([H|T], Counter):-
    columns(Columns),
    succ(Counter, C),
    M is C mod Columns,
    M \== 0,
    write(H),
    write(' '),
    write_grid(T, C).
write_grid([H|T], Counter):-
    columns(Columns),
    C is Counter + 1,
    M is C mod Columns,
    M == 0,
    write(H),
    ((rows(Rows),
      columns(Columns),
      Cells is Rows * Columns,
      C \== Cells,
      nl,
      write('\t'),
      write_grid(T, C)
     );
     (
      write_grid(T, C)
    )).

minecount(List, MineCount):-
    minecount(List, 0, MineCount).
minecount([], MineCount, MineCount).
minecount([H|T], MineCountPartial, MineCount):-  
    H == x,
    MCP is MineCountPartial + 1,
    minecount(T, MCP, MineCount).
minecount([H|T], MineCountPartial, MineCount):-  
    H \== x,
    minecount(T, MineCountPartial, MineCount).

adjacent_bottomleft(Cell, Grid, AdjacentCell):-
    columns(Columns),
    Columns1 is Columns - 1,
    C is Cell + Columns1,
    C > 0,
    M0 is Cell mod Columns,
    M1 is C mod Columns,
    ((M0 \== 0, M0 \==1, M1 < M0);
     (M0 == 0, M1 == Columns1)),
    nth(C, Grid, AdjacentCell).
adjacent_bottomleft(_, _, AdjacentCell):-
    AdjacentCell = null.

adjacent_left(Cell, Grid, AdjacentCell):-
    columns(Columns),
    Columns1 is Columns - 1,
    C is Cell - 1,
    C > 0,
    M0 is Cell mod Columns,
    M1 is C mod Columns,
    ((M0 \== 0, M0 \==1, M1 < M0);
     (M0 == 0, M1 == Columns1)),
    nth(C, Grid, AdjacentCell).
adjacent_left(_, _, AdjacentCell):-
    AdjacentCell = null.   

adjacent_topleft(Cell, Grid, AdjacentCell):-
    columns(Columns),
    Columns1 is Columns - 1,
    C is Cell - (Columns + 1),
    C > 0,
    M0 is Cell mod Columns,
    M1 is C mod Columns,
    ((M0 \== 0, M0 \==1, M1 < M0);
     (M0 == 0, M1 == Columns1)),
    nth(C, Grid, AdjacentCell).
adjacent_topleft(_, _, AdjacentCell):-
    AdjacentCell = null.  

adjacent_bottomright(Cell, Grid, AdjacentCell):-
    columns(Columns),
    Columns1 is Columns - 1,
    C is Cell + (Columns + 1),
    C > 0,
    M0 is Cell mod Columns,
    M1 is C mod Columns,
    ((M1 > M0, M0 \== 0);
     (M1 == 0, M0 == Columns1)),
    nth(C, Grid, AdjacentCell).
adjacent_bottomright(_, _, AdjacentCell):-
    AdjacentCell = null.          

adjacent_right(Cell, Grid, AdjacentCell):-
    columns(Columns),
    Columns1 is Columns - 1,
    C is Cell + 1,
    C > 0,
    M0 is Cell mod Columns,
    M1 is C mod Columns,
    ((M1 > M0, M0 \== 0);
     (M1 == 0, M0 == Columns1)),
    nth(C, Grid, AdjacentCell).
adjacent_right(_, _, AdjacentCell):-
    AdjacentCell = null.

adjacent_topright(Cell, Grid, AdjacentCell):-
    columns(Columns),
    Columns1 is Columns - 1,
    C is Cell - Columns1,
    M0 is Cell mod Columns,
    M1 is C mod Columns,
    ((M1 > M0, M0 \== 0);
     (M1 == 0, M0 == Columns1)),
    nth(C, Grid, AdjacentCell).
adjacent_topright(_, _, AdjacentCell):-
    AdjacentCell = null.    

adjacent_up(Cell, Grid, AdjacentCell):-
    columns(Columns),
    C is Cell - Columns,
    C > 0,
    nth(C, Grid, AdjacentCell).
adjacent_up(_, _, AdjacentCell):-
    AdjacentCell = null.    

adjacent_down(Cell, Grid, AdjacentCell):-
    columns(Columns),
    C is Cell + Columns,
    C > 0,
    nth(C, Grid, AdjacentCell).
adjacent_down(_, _, AdjacentCell):-
    AdjacentCell = null. 

adjacent(Cell, Grid, AdjacentCells):-
    adjacent_left(Cell, Grid, AdjacentCellLeft),
    adjacent_right(Cell, Grid, AdjacentCellRight),
    adjacent_up(Cell, Grid, AdjacentCellUp),
    adjacent_down(Cell, Grid, AdjacentCellDown),
    adjacent_topleft(Cell, Grid, AdjacentCellTopLeft),
    adjacent_topright(Cell, Grid, AdjacentCellTopRight),
    adjacent_bottomleft(Cell, Grid, AdjacentCellBottomLeft),
    adjacent_bottomright(Cell, Grid, AdjacentCellBottomRight),
    AdjacentCells = [AdjacentCellLeft, AdjacentCellRight, AdjacentCellUp, AdjacentCellDown,
                     AdjacentCellTopLeft, AdjacentCellTopRight, AdjacentCellBottomLeft, 
                     AdjacentCellBottomRight],!.

make_grid(Grid, NewGrid):-
    make_grid(Grid, 1, [], NewGrid). 
make_grid(Grid, Counter, NewGridPartial, NewGrid):-
    nth(Counter, Grid, CurrentCell),
    CurrentCell \== x,
    adjacent(Counter, Grid, AdjacentCells),
    minecount(AdjacentCells, MineCount),
    append(NewGridPartial, [MineCount], NGP),
    ((rows(Rows),
      columns(Columns),
      Cells is Rows * Columns,
      Counter == Cells, 
      !,
      NewGrid = NGP
    );
     (succ(Counter, C),
      make_grid(Grid, C, NGP, NewGrid))).
make_grid(Grid, Counter, NewGridPartial, NewGrid):-
    nth(Counter, Grid, CurrentCell),
    CurrentCell == x,
    append(NewGridPartial, [CurrentCell], NGP),
    ((rows(Rows),
      columns(Columns),
      Cells is Rows * Columns,
      Counter == Cells, 
      !,
      NewGrid = NGP
    );
     (succ(Counter, C),
      make_grid(Grid, C, NGP, NewGrid))).   

main:-
    grid(Grid),
    write('Input:'), nl,
    write_grid(Grid), nl,
    make_grid(Grid, NewGrid),
    write('Output:'), nl,
    write_grid(NewGrid), nl,
    halt.

Sample Run


$ gplc prolog/ch-2.p
$ prolog/ch-2
Input:
        x * * * x * x x x x
        * * * * * * * * * x
        * * * * x * x * x *
        * * * x x * * * * *
        x * * * x * * * * x
Output:
        x 1 0 1 x 2 x x x x
        1 1 0 2 2 4 3 5 5 x
        0 0 1 3 x 3 x 2 x 2
        1 1 1 x x 4 1 2 2 2
        x 1 1 3 x 2 0 0 1 x

Notes

For every cell C which does not contain a mine (x) we need to look at all eight adjacent cells and count the number of mines they contain. The number of mines in the adjacent cells is then set as C's label.

Obtaining the contents of the adjacent cells gets a little tedious. In fact, doing so is the majority of the code here. Care must be taken to make sure that we do not accidentally look for a cell which does not exist or is not actually adjacent. The logic for find the adjacent cells in this way is re-used from a coding challenge I did last year. The Advent of Code 2020 Day 11, in part, had a similar requirement.

After the logic of determining the contents of adjacent cells is worked out, the rest proceeds in a much less complicated way. The contents of all the adjacent cells are examined for mines and the cell labels are set appropriately.

References

Challenge 126

History of Minesweeper

Advent of Code 2020 Day 11

Prolog Solution: AoC 2020 Day 11 Part 1

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