module PlantSpec where import Test.Hspec import Terminal.Game import Input import Plant import Tile fakeTile :: Tile fakeTile = error "Plant - fakeTile" spec :: Spec spec = do describe "plantBoundaries" $ do it "returns correct val even it is not bottom-right" $ plantBoundaries (foldr (uncurry addTile) defaultPlant [((5,1), fakeTile), ((1, 10), fakeTile)]) `shouldBe` (5, 10) describe "gluePlants" $ do let t = Tile Solid (creaStaticAnimation $ cell 'x') p1 = addTile (1, 1) t defaultPlant p2 = addTile (1, 2) t defaultPlant g1 = gluePlants (2, 3) p1 [(W, p2)] g2 = gluePlants (2, 3) p1 [(W, p2), (S, p2)] it "does not modify main plant" $ getTile p1 (1, 1) `shouldBe` getTile g1 (1, 1) it "glues a single plant" $ getTile g1 (1, -1) `shouldBe` Just t it "glues multiple plants" $ getTile g2 (3, 2) `shouldBe` Just t it "glues multiple plants (Nothing)" $ getTile g2 (3, 3) `shouldBe` Nothing