Skip to content

Commit

Permalink
Add magic-square exercise
Browse files Browse the repository at this point in the history
  • Loading branch information
ErikSchierboom committed Sep 24, 2024
1 parent 33a2836 commit 48dcd28
Show file tree
Hide file tree
Showing 6 changed files with 115 additions and 0 deletions.
8 changes: 8 additions & 0 deletions config.json
Original file line number Diff line number Diff line change
Expand Up @@ -901,6 +901,14 @@
"practices": [],
"prerequisites": [],
"difficulty": 1
},
{
"slug": "magic-square",
"name": "Magic Square",
"uuid": "0dabf6ec-98fb-442c-9e1f-684108a67f26",
"practices": [],
"prerequisites": [],
"difficulty": 1
}
],
"foregone": [
Expand Down
14 changes: 14 additions & 0 deletions exercises/practice/magic-square/.docs/instructions.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
# Instructions

Your task is to, given a square of positive integers, determine if the square is a magic square.
A magic square is one where the sum of the numbers in each row, column and both diagonals are the same.

As an example, consider the following square:

```text
4 9 2
3 5 7
8 1 6
```

This is a magic square, as the sum of every row, column and both diagonals is equal to 15.
17 changes: 17 additions & 0 deletions exercises/practice/magic-square/.meta/config.json
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
{
"authors": [
"erikschierboom"
],
"files": {
"solution": [
"magic_square.pl"
],
"test": [
"magic_square_tests.plt"
],
"example": [
".meta/magic_square.example.pl"
]
},
"blurb": "Check if a square is a magic square"
}
23 changes: 23 additions & 0 deletions exercises/practice/magic-square/.meta/magic_square.example.pl
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
:- use_module(library(clpfd)).

diagonals(Rows, LeftRightDiagonal, RightLeftDiagonal) :-
length(Rows, N),
numlist(1, N, Indices),
reverse(Indices, ReverseIndices),
pairs_keys_values(LeftRightIndices, Indices, Indices),
pairs_keys_values(RightLeftIndices, ReverseIndices, Indices),
maplist(diagonal_element(Rows), LeftRightIndices, LeftRightDiagonal),
maplist(diagonal_element(Rows), RightLeftIndices, RightLeftDiagonal).

diagonal_element(Rows, X-Y, Value) :- nth1(Y, Rows, Row), nth1(X, Row, Value).

magic_square(Rows) :-
maplist(sumlist, Rows, RowSums),
transpose(Rows, Cols),
maplist(sumlist, Cols, ColSums),
diagonals(Rows, LeftRightDiagonal, RightLeftDiagonal),
sumlist(LeftRightDiagonal, LeftRightDiagonalSum),
sumlist(RightLeftDiagonal, RightLeftDiagonalSum),
append([RowSums, ColSums, [LeftRightDiagonalSum, RightLeftDiagonalSum]], Sums),
sort(Sums, SortedSums),
length(SortedSums, 1).
1 change: 1 addition & 0 deletions exercises/practice/magic-square/magic_square.pl
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
magic_square(Rows).
52 changes: 52 additions & 0 deletions exercises/practice/magic-square/magic_square_tests.plt
Original file line number Diff line number Diff line change
@@ -0,0 +1,52 @@
pending :-
current_prolog_flag(argv, ['--all'|_]).
pending :-
write('\nA TEST IS PENDING!\n'),
fail.

:- begin_tests(magic_square).

test(magic_square_order_3, condition(true)) :-
Square =
[
[2, 7, 6],
[9, 5, 1],
[4, 3, 8]
],
magic_square(Square).

test(magic_square_order_4, condition(true)) :-
Square =
[
[ 2, 16, 13, 3],
[11, 5, 8, 10],
[ 7, 9, 12, 6],
[14, 4, 1, 15]
],
magic_square(Square).

test(magic_square_order_9, condition(true)) :-
Square =
[
[31, 76, 13, 36, 81, 18, 29, 74, 11],
[22, 40, 58, 27, 45, 63, 20, 38, 56],
[67, 4, 49, 72, 9, 54, 65, 2, 47],
[30, 75, 12, 32, 77, 14, 34, 79, 16],
[21, 39, 57, 23, 41, 59, 25, 43, 61],
[66, 3, 48, 68, 5, 50, 70, 7, 52],
[35, 80, 17, 28, 73, 10, 33, 78, 15],
[26, 44, 62, 19, 37, 55, 24, 42, 60],
[71, 8, 53, 64, 1, 46, 69, 6, 51]
],
magic_square(Square).

test(invalid_magic_square, [fail, condition(pending)]) :-
Square =
[
[1, 2, 3],
[4, 5, 6],
[7, 8, 9]
],
magic_square(Square).

:- end_tests(magic_square).

0 comments on commit 48dcd28

Please sign in to comment.