{-# LANGUAGE QuasiQuotes #-} module Day7Spec (spec) where import Test.Hspec import Text.Heredoc import Shared import Day7.Parser import Day7.Interpreter import qualified Data.Map as Map inputPart1 :: String inputPart1 = [str|$ cd / |$ ls |dir a |14848514 b.txt |8504156 c.dat |dir d |$ cd a |$ ls |dir e |29116 f |2557 g |62596 h.lst |$ cd e |$ ls |584 i |$ cd .. |$ cd .. |$ cd d |$ ls |4060174 j |8033020 d.log |5626152 d.ext |7214296 k |] cdTerm :: [TerminalCommand] cdTerm = forceRight $ parseTerminalLines [str|$ cd foo |$ ls |23 f |34 f2 |dir d |$ cd .. |] cdOutTerm :: [TerminalCommand] cdOutTerm = forceRight $ parseTerminalLines [str|$ cd foo |$ ls |42 f |$ cd .. |$ cd bar |$ ls |100 baba |$ cd x |$ cd / |$ ls |23 f |dir foo |dir bar |] cdOutParsed :: [TerminalCommand] cdOutParsed = [ In "foo", Listing [FileListing "f" 42], Out, In "bar", Listing [FileListing "baba" 100], In "x", Root, Listing [FileListing "f" 23, DirListing "foo", DirListing "bar"] ] spec :: Spec spec = describe "Day7" $ do describe "Part1" $ do describe "parser" $ do it "parses an ls command" $ do parseTerminalLines "$ ls\n" `shouldBe` Right [Listing []] it "parses a cd up command" $ do parseTerminalLines "$ cd ..\n" `shouldBe` Right [Out] it "parses a cd root command" $ do parseTerminalLines "$ cd /\n" `shouldBe` Right [Root] it "parses a cd in command" $ do parseTerminalLines "$ cd dirname\n" `shouldBe` Right [In "dirname"] it "parses a file listing line" $ do parseTerminalLines "$ ls\n1234 f\n$ cd foo\n" `shouldBe` Right [Listing [FileListing "f" 1234], In "foo"] it "parses a larger shell log" $ do cdOutTerm `shouldBe` cdOutParsed describe "tree" $ do it "reads a listing" $ do buildTree [Listing [FileListing "f" 123]] `shouldBe` mkdir { files = Map.singleton "f" 123, isRoot = True } it "changes dir" $ do buildTree cdTerm `shouldBe` mkdir { sub = Map.fromList [ ("foo", mkdir { files = Map.fromList [("f", 23), ("f2", 34)] }) ], files = Map.empty, isRoot = True } it "changes dir outwards" $ do buildTree cdOutTerm `shouldBe` mkdir { sub = Map.fromList [ ("foo", mkdir { files = Map.fromList [("f", 42)] } ), ("bar", mkdir { sub = Map.fromList [("x", mkdir)], files = Map.fromList [("baba", 100)] } ) ], files = Map.fromList [("f", 23)], isRoot = True } it "calculates size of directories" $ do calculateSize mkdir { files = Map.fromList [("f", 23), ("f2", 34)] } `shouldBe` 23 + 34 calculateSize mkdir { sub = Map.fromList [ ("d", mkdir { files = Map.fromList [("f", 23), ("f2", 34)] })] } `shouldBe` 23 + 34 it "sums stuff up" $ do let parsed = forceRight $ parseTerminalLines inputPart1 let tree = buildTree parsed let filtered = filterDirectories (<= 100000) tree let summed = sum filtered summed `shouldBe` 95437