Skip to content

Instantly share code, notes, and snippets.

@qguv
Created April 11, 2015 17:01
Show Gist options
  • Save qguv/6e19171a4a4bf7a7b9f9 to your computer and use it in GitHub Desktop.
Save qguv/6e19171a4a4bf7a7b9f9 to your computer and use it in GitHub Desktop.
Knight Project Tests
module TestKnightPlace where
import Test.Hspec
import Data.Matrix (Matrix, matrix, mapCol, identity, getElem, zero)
import KnightPlace
-- a matrix of full of False with only one cell true
matrixOnly row col = matrix 4 4 (\(i, j) -> i == row && j == col)
-- a matrix of the given dimensions representing a function applied to each
-- element of the identity matrix
matrixId test dims =
let id = identity dims
in matrix dims dims $ \(i, j) -> test (getElem i j id)
-- a matrix of the given dimensions filled with the given thing
matrixFullOf fill dims = matrix dims dims (\_ -> fill)
-- a matrix full of False with the 1,1 true
originTrue dims = matrix dims dims (\(i, j) -> i == 1 && j == 1)
-- a matrix full of False with the middle element true
trueInMiddle dims = matrix dims dims (\(i, j) -> i == middle && j == middle)
where middle = (dims `div` 2) + 1
rowListToMatrix :: [[a]] -> Matrix a
rowListToMatrix rowList = matrix dims dims (\(i, j) -> (rowList !! (i - 1)) !! (j - 1))
where dims = length rowList
falseInX5 = rowListToMatrix [
[False, True, True, True, False],
[True, False, True, False, True ],
[True, True, False, True, True ],
[True, False, True, False, True ],
[False, True, True, True, False]]
falseKnights5 = rowListToMatrix [
[True, False, True, False, True ],
[False, True, True, True, False],
[True, True, True, True, True ],
[False, True, True, True, False],
[True, False, True, False, True ]]
main :: IO ()
main = hspec $ do
describe "toMatrix" $ do
it "can properly translate a one-queen 4x4 example (queen at 2,3)" $ do
toMatrix [0, 0, 2, 0] `shouldBe` (matrixOnly 2 3)
it "can properly translate a loaded 4x4 example (queens at id elements)" $ do
toMatrix [1, 2, 3, 4] `shouldBe` matrixId (== 1) 4
it "can handle an empty 4x4 example" $ do
toMatrix [0, 0, 0, 0] `shouldBe` matrixFullOf False 4
describe "fromMatrix" $ do
it "can properly translate a one-knight 4x4 example (knight at 2,3)" $ do
fromMatrix (matrixOnly 2 3) `shouldBe` [[0], [0], [2], [0]]
it "can properly translate a loaded 4x4 example (knights everywhere)" $ do
fromMatrix (matrixFullOf True 4) `shouldBe` replicate 4 [1, 2, 3, 4]
it "can handle an empty 4x4 example" $ do
fromMatrix (matrixFullOf False 4) `shouldBe` replicate 4 [0]
describe "rule1" $ do
it "allows knights in queen-absent columns and disallows knights in queen-present columns" $ do
rule1 (matrix 10 10 (\(i, j) -> i == 1 && j == 1)) `shouldBe` matrix 10 10 (\(_, j) -> j /= 1)
describe "rule2" $ do
it "allows knights in queen-absent rows and disallows knights in queen-present rows" $ do
rule2 (matrix 10 10 (\(i, j) -> i == 1 && j == 1)) `shouldBe` matrix 10 10 (\(i, _) -> i /= 1)
describe "inBounds" $ do
it "accepts elements with element/s at dimensions" $ do
inBounds 10 (10, 5) `shouldBe` True
inBounds 10 (5, 10) `shouldBe` True
inBounds 10 (10, 10) `shouldBe` True
it "accepts bounded elements" $ do
inBounds 10 (5, 5) `shouldBe` True
inBounds 10 (1, 3) `shouldBe` True
it "rejects elements with bounds at zero" $ do
inBounds 10 (0, 5) `shouldBe` False
inBounds 10 (5, 0) `shouldBe` False
inBounds 10 (0, 0) `shouldBe` False
it "rejects elements with bounds below zero" $ do
inBounds 10 (-1, 5) `shouldBe` False
inBounds 10 (5, -1) `shouldBe` False
inBounds 10 (-1, -1) `shouldBe` False
it "rejects elements with element/s above dimensions" $ do
inBounds 10 (11, 5) `shouldBe` False
inBounds 10 (5, 11) `shouldBe` False
inBounds 10 (11, 11) `shouldBe` False
describe "scootAround" $ do
it "scoots zero cells right" $ do
scootAround 10 (\(i, j) -> (i + 1, j)) (10, 5) `shouldBe` [(10, 5)]
it "scoots one cell right" $ do
scootAround 10 (\(i, j) -> (i + 1, j)) (9, 5) `shouldBe` [(9, 5), (10, 5)]
it "scoots two cells right" $ do
scootAround 10 (\(i, j) -> (i + 1, j)) (8, 5) `shouldBe` [(8, 5), (9, 5), (10, 5)]
it "scoots zero cells down and right" $ do
scootAround 10 (\(i, j) -> (i + 1, j + 1)) (10, 5) `shouldBe` [(10, 5)]
it "scoots one cell down and right" $ do
scootAround 10 (\(i, j) -> (i + 1, j + 1)) (9, 5) `shouldBe` [(9, 5), (10, 6)]
it "scoots two cells down and right" $ do
scootAround 10 (\(i, j) -> (i + 1, j + 1)) (8, 5) `shouldBe` [(8, 5), (9, 6), (10, 7)]
describe "rule3" $ do
it "disallows knights in an X pattern from a central queen" $ do
rule3 (trueInMiddle 5) `shouldBe` falseInX5
it "disallows knights in a slash pattern from a queen in a corner" $ do
rule3 (originTrue 5) `shouldBe` (matrixId (/= 1) 5)
describe "rule4" $ do
it "keeps knights from hurting a middle-queen" $ do
rule4 (trueInMiddle 5) `shouldBe` falseKnights5
describe "knightPlace" $ do
it "passes the (tougher) first test in the spec" $ do
knightPlace [0,0,6,0,0,4,0,0] `shouldBe` [[1,2,3],[1,2,3],[0],[1],[1],[0],[1,7,8],[7,8]]
it "passes the (simpler) second test in the spec" $ do
knightPlace [4, 0, 4, 4] `shouldBe` [[0], [1], [0], [0]]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment