123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384 |
- {-# LANGUAGE QuasiQuotes #-}
- module Day5Spec (spec) where
-
- import Test.Hspec
- import Text.Heredoc
- import qualified Data.Sequence as S
-
- import Day5.Part1
- import Day5.Part2
- import Day5.Shared
-
- inputPart1 :: String
- inputPart1 = [str| [D]
- |[N] [C]
- |[Z] [M] [P]
- | 1 2 3
- |
- |move 1 from 2 to 1
- |move 3 from 1 to 3
- |move 2 from 2 to 1
- |move 1 from 1 to 2
- |]
-
- inputStacks :: String
- inputStacks = [str| [D]
- |[N] [C]
- |[Z] [M] [P]
- | 1 2 3
- |]
-
- inputOperations :: String
- inputOperations = [str|move 1 from 2 to 1
- |move 3 from 1 to 3
- |move 2 from 2 to 1
- |move 1 from 1 to 2
- |]
- spec :: Spec
- spec =
- describe "Day5" $ do
- describe "Part1" $ do
- it "parses Operations" $ do
- let operation = head . lines $ inputOperations
- parseOperation operation `shouldBe` Operation { count = 1, from = StackIndex 2, to = StackIndex 1 }
- it "parses stacks" $ do
- parseStacks (lines inputStacks) `shouldBe` S.fromList [Stack "NZ", Stack "DCM", Stack "P"]
- it "parses a single line of stacks" $ do
- let row = head . lines $ inputStacks
- parseRow row `shouldBe` S.fromList [Stack "", Stack "D"]
- it "combines stacks" $ do
- (Stack "AB" <> Stack "CD") `shouldBe` Stack "ABCD"
- it "combines rows" $ do
- S.fromList [Stack "", Stack "A"] `combineRows` S.fromList [Stack "B", Stack "B"] `shouldBe` S.fromList [Stack "B", Stack "AB"]
- S.empty `combineRows` S.fromList [Stack "B", Stack "B"] `shouldBe` S.fromList [Stack "B", Stack "B"]
- S.fromList [Stack "A", Stack "B"] `combineRows` S.empty `shouldBe` S.fromList [Stack "A", Stack "B"]
- S.singleton (Stack "") `combineRows` S.fromList[Stack "B", Stack "B"] `shouldBe` S.fromList [Stack "B", Stack "B"]
- S.fromList [Stack "A", Stack "B"] `combineRows` S.singleton (Stack "") `shouldBe` S.fromList [Stack "A", Stack "B"]
- it "splits input into stacks and operations" $ do
- parseInput inputPart1 `shouldBe`
- (S.fromList [Stack "NZ", Stack "DCM", Stack "P"],
- [ Operation { count = 1, from = StackIndex 2, to = StackIndex 1},
- Operation { count = 3, from = StackIndex 1, to = StackIndex 3},
- Operation { count = 2, from = StackIndex 2, to = StackIndex 1},
- Operation { count = 1, from = StackIndex 1, to = StackIndex 2}])
- it "exeutes a count=1 operation on a row" $ do
- let op = Operation { count = 1, from = StackIndex 2, to = StackIndex 3}
- let row = S.fromList [Stack "NZ", Stack "DCM", Stack "P"]
- executeOperation row op `shouldBe` S.fromList [Stack "NZ", Stack "CM", Stack "DP"]
- it "exeutes a count > 1 operation on a row" $ do
- let op = Operation { count = 2, from = StackIndex 2, to = StackIndex 3}
- let row = S.fromList [Stack "NZ", Stack "DCM", Stack "P"]
- executeOperation row op `shouldBe` S.fromList [Stack "NZ", Stack "M", Stack "CDP"]
- it "finds the top items on stacks" $ do
- let row = S.fromList [Stack "NZ", Stack "DCM", Stack "P"]
- findTopOfStacks row `shouldBe` S.fromList "NDP"
- it "solves the demo" $ do
- day5_1 inputPart1 `shouldBe` "CMZ"
- describe "Part1" $ do
- it "executes 9001 operations on a row" $ do
- let op = Operation { count = 2, from = StackIndex 2, to = StackIndex 3}
- let row = S.fromList [Stack "NZ", Stack "DCM", Stack "P"]
- execute9001Operation row op `shouldBe` S.fromList [Stack "NZ", Stack "M", Stack "DCP"]
- it "solves the demo" $ do
- day5_2 inputPart1 `shouldBe` "MCD"
|