Skip to content

Commit

Permalink
Add game-of-life exercise (#450)
Browse files Browse the repository at this point in the history
  • Loading branch information
ErikSchierboom authored Oct 19, 2024
1 parent a974124 commit 5aa3e2b
Show file tree
Hide file tree
Showing 8 changed files with 224 additions and 0 deletions.
8 changes: 8 additions & 0 deletions config.json
Original file line number Diff line number Diff line change
Expand Up @@ -917,6 +917,14 @@
"practices": [],
"prerequisites": [],
"difficulty": 1
},
{
"slug": "game-of-life",
"name": "Conway's Game of Life",
"uuid": "a5fb2249-46ec-4e6e-bc4f-947f0e0a7193",
"practices": [],
"prerequisites": [],
"difficulty": 4
}
],
"foregone": [
Expand Down
11 changes: 11 additions & 0 deletions exercises/practice/game-of-life/.docs/instructions.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
# Instructions

After each generation, the cells interact with their eight neighbors, which are cells adjacent horizontally, vertically, or diagonally.

The following rules are applied to each cell:

- Any live cell with two or three live neighbors lives on.
- Any dead cell with exactly three live neighbors becomes a live cell.
- All other cells die or stay dead.

Given a matrix of 1s and 0s (corresponding to live and dead cells), apply the rules to each cell, and return the next generation.
9 changes: 9 additions & 0 deletions exercises/practice/game-of-life/.docs/introduction.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
# Introduction

[Conway's Game of Life][game-of-life] is a fascinating cellular automaton created by the British mathematician John Horton Conway in 1970.

The game consists of a two-dimensional grid of cells that can either be "alive" or "dead."

After each generation, the cells interact with their eight neighbors via a set of rules, which define the new generation.

[game-of-life]: https://en.wikipedia.org/wiki/Conway%27s_Game_of_Life
19 changes: 19 additions & 0 deletions exercises/practice/game-of-life/.meta/config.json
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
{
"authors": [
"erikschierboom"
],
"files": {
"solution": [
"game_of_life.pl"
],
"test": [
"game_of_life_tests.plt"
],
"example": [
".meta/game_of_life.example.pl"
]
},
"blurb": "Implement Conway's Game of Life.",
"source": "Wikipedia",
"source_url": "https://en.wikipedia.org/wiki/Conway%27s_Game_of_Life"
}
27 changes: 27 additions & 0 deletions exercises/practice/game-of-life/.meta/game_of_life.example.pl
Original file line number Diff line number Diff line change
@@ -0,0 +1,27 @@
:- use_module(library(clpfd)).

cell(Rows, X, Y, Cell) :- nth1(Y, Rows, Row), nth1(X, Row, Cell).

live_neighbor(Rows, X, Y) :-
between(-1, 1, Dx),
between(-1, 1, Dy),
NeighborX #= X + Dx,
NeighborY #= Y + Dy,
(NeighborX #\= X #\/ NeighborY #\= Y),
cell(Rows, NeighborX, NeighborY, 1).

next_cell(Rows, Y, Cell, X, NextCell) :-
findall(1, live_neighbor(Rows, X, Y), LiveNeighbors),
length(LiveNeighbors, Count),
(Count #= 3; Count #= 2, Cell = 1) -> NextCell = 1; NextCell = 0.

next_row(Rows, Y, Row, NextRow) :-
length(Row, Length),
numlist(1, Length, Xs),
maplist(next_cell(Rows, Y), Row, Xs, NextRow).

tick([], []) :- !.
tick(Current, Next) :-
length(Current, Height),
numlist(1, Height, Ys),
maplist(next_row(Current), Ys, Current, Next).
34 changes: 34 additions & 0 deletions exercises/practice/game-of-life/.meta/tests.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1,34 @@
# This is an auto-generated file.
#
# Regenerating this file via `configlet sync` will:
# - Recreate every `description` key/value pair
# - Recreate every `reimplements` key/value pair, where they exist in problem-specifications
# - Remove any `include = true` key/value pair (an omitted `include` key implies inclusion)
# - Preserve any other key/value pair
#
# As user-added comments (using the # character) will be removed when this file
# is regenerated, comments can be added via a `comment` key.

[ae86ea7d-bd07-4357-90b3-ac7d256bd5c5]
description = "empty matrix"

[4ea5ccb7-7b73-4281-954a-bed1b0f139a5]
description = "live cells with zero live neighbors die"

[df245adc-14ff-4f9c-b2ae-f465ef5321b2]
description = "live cells with only one live neighbor die"

[2a713b56-283c-48c8-adae-1d21306c80ae]
description = "live cells with two live neighbors stay alive"

[86d5c5a5-ab7b-41a1-8907-c9b3fc5e9dae]
description = "live cells with three live neighbors stay alive"

[015f60ac-39d8-4c6c-8328-57f334fc9f89]
description = "dead cells with three live neighbors become alive"

[2ee69c00-9d41-4b8b-89da-5832e735ccf1]
description = "live cells with four or more neighbors die"

[a79b42be-ed6c-4e27-9206-43da08697ef6]
description = "bigger matrix"
1 change: 1 addition & 0 deletions exercises/practice/game-of-life/game_of_life.pl
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
tick(Current, Next).
115 changes: 115 additions & 0 deletions exercises/practice/game-of-life/game_of_life_tests.plt
Original file line number Diff line number Diff line change
@@ -0,0 +1,115 @@
pending :-
current_prolog_flag(argv, ['--all'|_]).
pending :-
write('\nA TEST IS PENDING!\n'),
fail.

:- begin_tests(game_of_life).

test(empty_matrix, condition(true)) :-
Current = [],
tick(Current, Next),
Next == [].

test(live_cells_with_zero_live_neighbors_die, condition(pending)) :-
Current = [
[0, 0, 0],
[0, 1, 0],
[0, 0, 0]
],
tick(Current, Next),
Next == [
[0, 0, 0],
[0, 0, 0],
[0, 0, 0]
].

test(live_cells_with_only_one_live_neighbor_die, condition(pending)) :-
Current = [
[0, 0, 0],
[0, 1, 0],
[0, 1, 0]
],
tick(Current, Next),
Next == [
[0, 0, 0],
[0, 0, 0],
[0, 0, 0]
].

test(live_cells_with_two_live_neighbors_stay_alive, condition(pending)) :-
Current = [
[1, 0, 1],
[1, 0, 1],
[1, 0, 1]
],
tick(Current, Next),
Next == [
[0, 0, 0],
[1, 0, 1],
[0, 0, 0]
].

test(live_cells_with_three_live_neighbors_stay_alive, condition(pending)) :-
Current = [
[0, 1, 0],
[1, 0, 0],
[1, 1, 0]
],
tick(Current, Next),
Next == [
[0, 0, 0],
[1, 0, 0],
[1, 1, 0]
].

test(dead_cells_with_three_live_neighbors_become_alive, condition(pending)) :-
Current = [
[1, 1, 0],
[0, 0, 0],
[1, 0, 0]
],
tick(Current, Next),
Next == [
[0, 0, 0],
[1, 1, 0],
[0, 0, 0]
].

test(live_cells_with_four_or_more_neighbors_die, condition(pending)) :-
Current = [
[1, 1, 1],
[1, 1, 1],
[1, 1, 1]
],
tick(Current, Next),
Next == [
[1, 0, 1],
[0, 0, 0],
[1, 0, 1]
].

test(bigger_matrix, condition(pending)) :-
Current = [
[1, 1, 0, 1, 1, 0, 0, 0],
[1, 0, 1, 1, 0, 0, 0, 0],
[1, 1, 1, 0, 0, 1, 1, 1],
[0, 0, 0, 0, 0, 1, 1, 0],
[1, 0, 0, 0, 1, 1, 0, 0],
[1, 1, 0, 0, 0, 1, 1, 1],
[0, 0, 1, 0, 1, 0, 0, 1],
[1, 0, 0, 0, 0, 0, 1, 1]
],
tick(Current, Next),
Next == [
[1, 1, 0, 1, 1, 0, 0, 0],
[0, 0, 0, 0, 0, 1, 1, 0],
[1, 0, 1, 1, 1, 1, 0, 1],
[1, 0, 0, 0, 0, 0, 0, 1],
[1, 1, 0, 0, 1, 0, 0, 1],
[1, 1, 0, 1, 0, 0, 0, 1],
[1, 0, 0, 0, 0, 0, 0, 0],
[0, 0, 0, 0, 0, 0, 1, 1]
].

:- end_tests(game_of_life).

0 comments on commit 5aa3e2b

Please sign in to comment.