module Line.DrawSpec where import Line.Draw import Test.Hspec import Test.QuickCheck main :: IO () main = hspec spec spec :: Spec spec = do describe "bresenham (hspec)" $ do it "rasterises a simple line" $ bresenham (0 :: Int, 0) (4, 4) `shouldBe` [(0,0), (1,1), (2,2), (3,3), (4,4)] it "rasterises a simple line starting from (1, 1)" $ bresenham (1 :: Int, 1) (4, 4) `shouldBe` [(1,1), (2,2), (3,3), (4,4)] it "rasterises a line" $ bresenham (0 :: Int, 0) (4, 2) `shouldBe` [(0,0), (1,0), (2,1), (3,1), (4,2)] it "rasterises a line, quadrant 2, m<1" $ bresenham (0 :: Int, 0) (-4, 2) `shouldBe` [(0,0), (-1,0), (-2,1), (-3,1), (-4,2)] it "rasterises a line, quadrant 3, m<1" $ bresenham (0 :: Int, 0) (-4, -2) `shouldBe` [(0,0), (-1,0), (-2,-1), (-3,-1), (-4,-2)] it "rasterises a line, quadrant 1, m>1" $ bresenham (0 :: Int, 0) (2, 4) `shouldBe` [(0,0), (0,1), (1,2), (1,3), (2,4)] it "rasterises a line, quadrant 4, m>1" $ bresenham (0 :: Int, 0) (2, -4) `shouldBe` [(0,0), (0,-1), (1,-2), (1,-3), (2,-4)] it "returns a singleton list if start and end are the same" $ bresenham (2 :: Int, 2) (2, 2) `shouldBe` [(2,2)] it "does not get confused with points on second quadrant" $ bresenham (13 :: Int, 17) (12, 18) `shouldBe` [(13,17), (12,18)] describe "bresenham (quickcheck)" $ do it "does never return an empty list" $ property $ \(p1, p2) -> length (bresenham (p1 :: (Int, Int)) p2) /= 0 it "is the same length with args flipped" $ property $ \(p1, p2) -> length (bresenham (p1 :: (Int, Int)) p2) == length (bresenham p2 p1) it "has a distance of 1 if the points are the same" $ property $ \p -> length (bresenham (p :: (Int, Int)) p) == 1