diff --git a/.dir-locals.el b/.dir-locals.el index 98e4ff8..a1faec5 100644 --- a/.dir-locals.el +++ b/.dir-locals.el @@ -7,3 +7,4 @@ + diff --git a/adventofcode.cabal b/adventofcode.cabal index b091949..9286c9a 100644 --- a/adventofcode.cabal +++ b/adventofcode.cabal @@ -2,7 +2,7 @@ -- -- see: https://github.com/sol/hpack -- --- hash: 454d3692225cbc9c59993888515dbf7f9c46a2d886ffebc91072c08157888c4d +-- hash: ece24a6f206c14c1251a73fcaadfb901287003b3dc6bb86e59bb0df886d7d33d name: adventofcode version: 0.1.0.0 @@ -79,6 +79,7 @@ test-suite adventofcode-test HUnit , adventofcode , base + , protolude , tasty , tasty-hunit other-modules: diff --git a/app/Main.hs b/app/Main.hs index f2cf0ee..3e72375 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -10,6 +10,8 @@ import qualified Data.Map as Map import qualified Day01 import qualified Day02 +import qualified Day03 +import qualified Day04 import qualified Day05 import qualified Day06 import qualified Day07 @@ -34,6 +36,8 @@ main = do solutions :: Map [[Char]] (IO ()) solutions = Map.fromList [(["01"], day01) ,(["02"], day02) + ,(["03"], day03) + ,(["04"], day04) ,(["05"], day05) ,(["06"], day06) ,(["07"], day07) @@ -45,6 +49,12 @@ solutions = Map.fromList [(["01"], day01) ,(["13"], day13) ] + +-- | Show ZERO in case of failure +mint = int . fromMaybe 0 +-- | Show ZERO in case of failure +minteger = integer . fromMaybe 0 + day01 :: IO () day01 = do putText "Day 01:" @@ -61,6 +71,21 @@ day02 = do let sol2 = maybe 0 Day02.solution2 input showSol "Solution 2" (integer sol2) +day03 :: IO () +day03 = do + putText "Day 03:" + showSol "Solution 1" (minteger (Day03.solution1 Day03.input)) + showSol "Solution 2" (minteger (Day03.solution2 (fromIntegral Day03.input))) + +day04 :: IO () +day04 = do + putText "Day 04:" + input <- Day04.parseInput + let sol1 = Day04.solution1 input + showSol "Solution 1" (int sol1) + let sol2 = Day04.solution2 input + showSol "Solution 2" (int sol2) + day05 :: IO () day05 = do putText "Day 05:" @@ -99,9 +124,10 @@ day08 = do day09 :: IO () day09 = do putText "Day 09:" - sol1 <- Day09.solution1 + input <- Day09.parseInput + let sol1 = Day09.solution1 input showSol "Solution 1" (int sol1) - sol2 <- Day09.solution2 + let sol2 = Day09.solution2 input showSol "Solution 2" (int sol2) day10 :: IO () diff --git a/package.yaml b/package.yaml index befc5b0..6b4b183 100644 --- a/package.yaml +++ b/package.yaml @@ -59,6 +59,7 @@ tests: - -rtsopts - -with-rtsopts=-N dependencies: + - protolude - base - adventofcode - tasty diff --git a/src/Day03.hs b/src/Day03.hs index ac4ea3d..80e438c 100644 --- a/src/Day03.hs +++ b/src/Day03.hs @@ -57,6 +57,7 @@ import qualified Control.Foldl as F import Data.List (words,lines) import qualified Data.Map as Map +input :: Int input = 265149 @@ -78,11 +79,14 @@ block1 = [ (2,1,0) ] spiral = (1,0,0):concatMap (\n -> blocks (n+1) ((n+1)^2,n `div` 2,- (n `div` 2))) [0,2..] +returnPathLength :: Int -> Maybe Integer returnPathLength i = drop (i - 1) spiral & head & fmap (\(_,x,y) -> abs x + abs y) +solution1 :: Int -> Maybe Integer +solution1 = returnPathLength -- Solution 2 @@ -95,7 +99,7 @@ spiralDebug = go Map.empty (0,0) in (val,nextcoord,neigh):go nextspiral nextcoord spiral2 = map (\(x,_,_) -> x) spiralDebug -solution2 = head $ dropWhile (< 265149) spiral2 +solution2 input = head $ dropWhile (< input) spiral2 neighbor :: Spiral -> (Int,Int) -> [Maybe Integer] neighbor spiral (x,y) = diff --git a/src/Day04.hs b/src/Day04.hs index 2282279..094ca3f 100644 --- a/src/Day04.hs +++ b/src/Day04.hs @@ -40,9 +40,10 @@ import Protolude import qualified Data.Text as Text parseInput :: IO [[Text]] -parseInput = do - inputTxt <- readFile "inputs/day4.txt" - return $ inputTxt & Text.lines & map Text.words +parseInput = parseTxt <$> readFile "inputs/day4.txt" + +parseTxt :: Text -> [[Text]] +parseTxt txt = txt & Text.lines & map Text.words allUniq :: Eq a => [a] -> Bool allUniq [] = True diff --git a/src/Day09.hs b/src/Day09.hs index 401ddf6..350a674 100644 --- a/src/Day09.hs +++ b/src/Day09.hs @@ -84,15 +84,16 @@ How many non-canceled characters are within the garbage in your puzzle input? |-} module Day09 where -import Protolude hiding ((<|>),many) +import Protolude hiding ((<|>)) import qualified Data.Map.Strict as Map import Text.Parsec -solution1 :: IO Int -solution1 = do - str <- readFile "inputs/day9.txt" - return $ either (const 0) identity (parseGroups str) +parseInput :: IO Text +parseInput = readFile "inputs/day9.txt" + +solution1 :: Text -> Int +solution1 str = either (const 0) identity (parseGroups str) parseGroups :: Text -> Either ParseError Int parseGroups = runParser groups (0,0) "Groups 1" @@ -101,7 +102,7 @@ groups :: Parsec Text (Int,Int) Int groups = do c <- char '{' updateState (\(d,s) -> (d+1,s+d+1)) - (groups <|> garbage) `sepBy` (char ',') + (groups <|> garbage) `sepBy` char ',' c <- char '}' updateState (\(d,s) -> (d-1,s)) fmap snd getState @@ -119,11 +120,8 @@ garbage = do '!' -> anyChar >> endGarbage _ -> endGarbage - -solution2 :: IO Int -solution2 = do - str <- readFile "inputs/day9.txt" - return $ either (const 0) identity (parseGroups2 str) +solution2 :: Text -> Int +solution2 txt = either (const 0) identity (parseGroups2 txt) parseGroups2 :: Text -> Either ParseError Int parseGroups2 = runParser groups2 0 "Groups 2" diff --git a/test/Spec.hs b/test/Spec.hs index eb7a528..aca09cf 100644 --- a/test/Spec.hs +++ b/test/Spec.hs @@ -1,4 +1,5 @@ {-# LANGUAGE OverloadedStrings #-} +import Protolude import Test.Tasty import Test.Tasty.HUnit @@ -6,10 +7,13 @@ import Control.Monad (when) import qualified Day01 import qualified Day02 +import qualified Day03 +import qualified Day04 import qualified Day05 import qualified Day06 import qualified Day07 import qualified Day08 +import qualified Day09 import qualified Day10 import qualified Day11 import qualified Day12 @@ -18,7 +22,41 @@ import qualified Day13 main :: IO () main = defaultMain $ testGroup "Advent Of Code 2017" - [ + [ testDay01 + , testDay02 + , testDay03 + , testDay04 + , testDay05 + , testDay06 + , testDay07 + , testDay08 + , testDay09 + , testDay10 + , testGroup "Day 12" + [ testGroup "Solution 1" + [ testCase "Example" $ + fmap Day12.solution1 (Day12.parseTxt Day12.testTxt) @?= Just 6 + ] + , testGroup "Solution 2" + [ testCase "Example" $ + fmap Day12.solution2 (Day12.parseTxt Day12.testTxt) @?= Just 2 + ] + ] + , testGroup "Day 13" + [ testGroup "Solution 1" + [ testCase "Example" $ + (Day13.solution1 . Day13.mkAppState) + <$> Day13.parseTxt Day13.testInput + @?= Just 24 + ] + , testGroup "Solution 2" + [ testCase "Example" $ + fmap Day13.solution2 (Day13.parseTxt Day13.testInput) @?= Just 10 + ] + ] + ] + +testDay01 = testGroup "Day 1" [ testGroup "solution 1" [ testCase "1122 is 3" $ Day01.solution1 "1122" @?= 3 @@ -34,27 +72,73 @@ main = defaultMain $ , testCase "12131415 is 4" $ Day01.solution2 "12131415" @?= 4 ] ] - , testGroup "Day 2" - [ testCase "example problem 1" $ - Day02.solution1 [[5,1,9,5],[7,5,3],[2,4,6,8]] @?= 18 - , testCase "example problem 2" $ - Day02.solution2 [[5,9,2,8],[9,4,7,3],[3,8,6,5]] @?= 9 + +testDay02 = + testGroup "Day 2" + [ testCase "example problem 1" $ + Day02.solution1 [[5,1,9,5],[7,5,3],[2,4,6,8]] @?= 18 + , testCase "example problem 2" $ + Day02.solution2 [[5,9,2,8],[9,4,7,3],[3,8,6,5]] @?= 9 + ] + +testDay03 = + testGroup "Day 3" + [ testGroup "Solution 1" + [ testCase "1" $ Day03.returnPathLength 1 @?= Just 0 + , testCase "12" $ Day03.returnPathLength 12 @?= Just 3 + , testCase "23" $ Day03.returnPathLength 23 @?= Just 2 + , testCase "1024" $ Day03.returnPathLength 1024 @?= Just 31 ] - , testGroup "Day 5" - [ testCaseSteps "example problem 1" $ \step -> do - step "Loading input" - input <- Day05.testArray - step "Running solution 1" - sol1 <- Day05.solution1 input - when (sol1 /= 5) (assertFailure "Should be 5 steps") - , testCaseSteps "example problem 2" $ \step -> do - step "Loading input" - input <- Day05.testArray - step "Running solution 2" - sol2 <- Day05.solution2 input - when (sol2 /= 10) (assertFailure "Day 6 solution 2 on the example should be 4") + , testGroup "Solution 2" + [ testCase "2" $ Day03.solution2 2 @?= Just 2 + , testCase "3" $ Day03.solution2 3 @?= Just 4 + , testCase "4" $ Day03.solution2 4 @?= Just 4 + , testCase "6" $ Day03.solution2 6 @?= Just 10 + , testCase "747" $ Day03.solution2 747 @?= Just 747 + , testCase "748" $ Day03.solution2 748 @?= Just 806 + , testCase "800" $ Day03.solution2 800 @?= Just 806 + , testCase "805" $ Day03.solution2 805 @?= Just 806 + , testCase "806" $ Day03.solution2 806 @?= Just 806 ] - , testGroup "Day 6" + ] + +testDay04 = + testGroup "Day 4" + [ testGroup "Solution 1" + [ testCase "1" $ Day04.solution1 (Day04.parseTxt testTxt) @?= 2 ] + , testGroup "Solution 2" + [ testCase "2" $ Day04.solution2 (Day04.parseTxt testTxt2) @?= 3 ] + ] + where + testTxt = "aa bb cc dd ee\n\ + \aa bb cc dd aa\n\ + \aa bb cc dd aaa\n" + testTxt2 = "abcde fghij\n\ + \abcde xyz ecdab\n\ + \a ab abc abd abf abj\n\ + \iiii oiii ooii oooi oooo\n\ + \oiii ioii iioi iiio\n" + +testDay05 = + testGroup "Day 5" + [ testCaseSteps "example problem 1" $ \step -> do + step "Loading input" + input <- Day05.testArray + step "Running solution 1" + sol1 <- Day05.solution1 input + when (sol1 /= 5) + (assertFailure "Should be 5 steps") + , testCaseSteps "example problem 2" $ \step -> do + step "Loading input" + input <- Day05.testArray + step "Running solution 2" + sol2 <- Day05.solution2 input + when (sol2 /= 10) + (assertFailure "Day 6 solution 2 on the example should be 4") + ] + +testDay06 = + testGroup "Day 6" [ testCaseSteps "example problem 1" $ \step -> do step "Loading input" input <- Day06.testArray @@ -68,7 +152,9 @@ main = defaultMain $ sol2 <- Day06.solution2 input when (sol2 /= 4) (assertFailure "Day 6 solution 2 on the example should be 4") ] - , testGroup "Day 7" + +testDay07 = + testGroup "Day 7" [ testCaseSteps "example problem 1" $ \step -> do step "Running solution 1" let input = Day07.testNodes @@ -77,56 +163,73 @@ main = defaultMain $ , testCase "example on solution 2" $ maybe 0 snd (Day07.solution2 Day07.testNodes) @?= 60 ] - , testGroup "Day 8" + +testDay08 = + testGroup "Day 8" [ testCase "example problem 1" $ Day08.solution1 Day08.testInstructions @?= 1 , testCase "example problem 1" $ Day08.solution2 Day08.testInstructions @?= 10 ] - , testGroup "Day 10" - [ testCase "example 1" $ - Day10.solution1 Day10.testInput @?= 12 - , testCase "solution 2 empty" $ - Day10.solution2 "" @?= "a2582a3a0e66e6e86e3812dcb672a272" - , testCase "solution 2 AoC 2017" $ - Day10.solution2 "AoC 2017" @?= "33efeb34ea91902bb2f59c9920caa6cd" - , testCase "solution 2 1,2,3" $ - Day10.solution2 "1,2,3" @?= "3efbe78a8d82f29979031a4aa0b16a9d" - , testCase "solution 2 1,2,4" $ - Day10.solution2 "1,2,4" @?= "63960835bcdc130f0b66d7ff4f6a5a8e" + +testDay09 = + testGroup "Day 9" + [ testGroup "Solution 1" + [ check1 "{}" 1 + , check1 "{{{}}}" 6 + , check1 "{{},{}}" 5 + , check1 "{{{},{},{{}}}}" 16 + , check1 "{,,,}" 1 + , check1 "{{},{},{},{}}" 9 + , check1 "{{},{},{},{}}" 9 + , check1 "{{},{},{},{}}" 3 ] - , testGroup "Day 11" - [ testGroup "Solution 1" - [ testCase "Example 1" $ - Day11.solution1 (Day11.parseTxt "ne,ne,ne") @?= 3 - , testCase "Example 2" $ - Day11.solution1 (Day11.parseTxt "ne,ne,sw,sw") @?= 0 - , testCase "Example 3" $ - Day11.solution1 (Day11.parseTxt "ne,ne,s,s") @?= 2 - , testCase "Example 4" $ - Day11.solution1 (Day11.parseTxt "se,sw,se,sw,sw") @?= 3 - ] + , testGroup "Solution 2" + [ check2 "<>" 0 + , check2 "" 17 + , check2 "<<<<>" 3 + , check2 "<{!>}>" 2 + , check2 "" 0 + , check2 ">" 0 + , check2 "<{o\"i!a,<{i" 10 ] - , testGroup "Day 12" - [ testGroup "Solution 1" - [ testCase "Example" $ - fmap Day12.solution1 (Day12.parseTxt Day12.testTxt) @?= Just 6 - ] - , testGroup "Solution 2" - [ testCase "Example" $ - fmap Day12.solution2 (Day12.parseTxt Day12.testTxt) @?= Just 2 + ] + where + check1 txt v = testCase (toS txt) (Day09.solution1 txt @?= v) + check2 txt v = testCase (toS txt) (Day09.solution2 ("{" <> txt <> "}") @?= v) + +testDay10 = + testGroup "Day 10" + [ testGroup "Solution 1" + [ testCase "example 1" $ Day10.solution1 Day10.testInput @?= 12 ] + , testGroup "Solution 2" + [check2 "" "a2582a3a0e66e6e86e3812dcb672a272" + , check2 "AoC 2017" "33efeb34ea91902bb2f59c9920caa6cd" + , check2 "1,2,3" "3efbe78a8d82f29979031a4aa0b16a9d" + , check2 "1,2,4" "63960835bcdc130f0b66d7ff4f6a5a8e" + ] + ] + where + check2 txt v = testCase (toS ("\"" <> txt <> "\"")) + (Day10.solution2 txt @?= v) + +testDay11 = + testGroup "Day 11" + [ testGroup "Solution 1" + [ check1 "ne,ne,ne" 3 + , check1 "ne,ne,sw,sw" 0 + , check1 "ne,ne,s,s" 2 + , check1 "se,sw,se,sw,sw" 3 ] + , testGroup "Solution 2" + [ check2 "ne,ne,ne" 3 + , check2 "ne,ne,sw,sw" 2 + , check2 "ne,ne,s,s" 2 + , check2 "se,sw,se,sw,sw" 3 ] - , testGroup "Day 13" - [ testGroup "Solution 1" - [ testCase "Example" $ - fmap Day13.solution1 - (fmap Day13.mkAppState - (Day13.parseTxt Day13.testInput)) @?= Just 24 - ] - , testGroup "Solution 2" - [ testCase "Example" $ - fmap Day13.solution2 (Day13.parseTxt Day13.testInput) @?= Just 10 - ] ] - ] + where + check1 txt v = testCase (toS txt) + (Day11.solution1 (Day11.parseTxt txt) @?= v) + check2 txt v = testCase (toS txt) + (Day11.solution2 (Day11.parseTxt txt) @?= v)