| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102 | {-# LANGUAGE QuasiQuotes #-}
module Day9Spec (spec) where
import Control.Arrow ((>>>))
import Day9
import Test.Hspec
import Text.Heredoc
import Data.List (sort)
testInput :: String
testInput =
  [str|R 4
                |U 4
                |L 3
                |D 1
                |R 4
                |D 1
                |L 5
                |R 2
                |]
expectedPositions :: [(Int, Int)]
expectedPositions = sort [
              (2,4),(3,4),
                    (3,3),(4,3),
        (1,2),(2,2),(3,2),(4,2),
                          (4,1),
  (0,0),(1,0),(2,0),(3,0)
  ]
testInput2 :: String
testInput2 = [str|R 5
                 |U 8
                 |L 8
                 |D 3
                 |R 17
                 |D 10
                 |L 25
                 |U 20
                 |]
spec :: Spec
spec =
  describe "Day9" $ do
    describe "Part1" $ do
      it "parses the instructions" $ do
        parseMovements testInput
          `shouldBe` [ right 4,
                       up 4,
                       left 3,
                       down 1,
                       right 4,
                       down 1,
                       left 5,
                       right 2
                     ]
      it "moves a step" $ do
        step (0, 0) (Step (1, 1)) `shouldBe` (1, 1)
        step (0, 0) (Step (1, 0)) `shouldBe` (1, 0)
        step (1, 0) (Step (-1, 0)) `shouldBe` (0, 0)
        step (0, 1) (Step (0, -1)) `shouldBe` (0, 0)
      it "normalizes movement" $ do
        normalizeMovement still `shouldBe` []
        normalizeMovement (left 2) `shouldBe` [Step (-1, 0),Step (-1, 0)]
        normalizeMovement (right 1) `shouldBe` [Step (1, 0)]
        normalizeMovement (up 1) `shouldBe` [Step (0, 1)]
        normalizeMovement (down 2) `shouldBe` [Step (0, -1), Step (0, -1)]
      it "follows the head" $ do
        follow (1, 0) (0, 0) `shouldBe` Step (0, 0)
        follow (0, 1) (0, 0) `shouldBe` Step (0, 0)
        follow (1, 1) (0, 0) `shouldBe` Step (0, 0)
        follow (2, 1) (0, 0) `shouldBe` Step (1, 1)
        follow (1, 2) (0, 0) `shouldBe` Step (1, 1)
        follow (2, 2) (0, 0) `shouldBe` Step (1, 1)
        follow (4, 2) (3, 0) `shouldBe` Step (1, 1)
      it "moves around and records tail position" $ do
        let positions = parseMovements
                >>> concatMap normalizeMovement
                >>> recordPositions
                >>> fst
                >>> sort
                $ testInput
        length positions `shouldBe` 13
        positions `shouldBe` expectedPositions
      it "solves the riddle" $ do
        input <- readFile "ressources/day09-input"
        let headSteps = parseMovements >>> concatMap normalizeMovement $ input
        let allTails = buildTails headSteps
        let positions = (!! 1)  >>> fst >>> length $ allTails
        positions `shouldBe` 5878
      it "solves example of part 2" $ do
        let headSteps = parseMovements >>> concatMap normalizeMovement $ testInput2
        let allTails = buildTails headSteps
        let tail9Positions = fst $ allTails !! 9
        length tail9Positions `shouldBe` 36
      it "solves the riddle part 2" $ do
        input <- readFile "ressources/day09-input"
        let headSteps = parseMovements >>> concatMap normalizeMovement $ input
        let allTails = buildTails headSteps
        let positions = (!! 9)  >>> fst >>> length $ allTails
        positions `shouldBe` 2405
 |