This commit is contained in:
Yann Esposito (Yogsototh) 2017-12-11 16:36:18 +01:00
parent 31a1dceadd
commit 0282a28f70
Signed by untrusted user who does not match committer: yogsototh
GPG key ID: 7B19A4C650D59646
7 changed files with 126 additions and 0 deletions

View file

@ -5,3 +5,5 @@
(intero-targets "adventofcode:lib" "adventofcode:exe:adventofcode-exe" "adventofcode:test:adventofcode-test")))

View file

@ -38,6 +38,7 @@ library
Day08
Day09
Day10
Day11
other-modules:
Paths_adventofcode
build-depends:

View file

@ -16,6 +16,7 @@ import qualified Day07
import qualified Day08
import qualified Day09
import qualified Day10
import qualified Day11
showSol :: [Char] -> Doc -> IO ()
showSol txt d = putText . toS . render $
@ -37,6 +38,7 @@ solutions = Map.fromList [(["01"], day01)
,(["08"], day08)
,(["09"], day09)
,(["10"], day10)
,(["11"], day11)
]
day01 :: IO ()
@ -105,3 +107,10 @@ day10 = do
showSol "Solution 1" (int sol1)
input2 <- Day10.parseInput2
showSol "Solution 2" (text (toS (Day10.solution2 input2)))
day11 :: IO ()
day11 = do
putText "Day 11:"
input <- Day11.parseInput
let sol1 = Day11.solution1 input
showSol "Solution 1" (int sol1)

1
inputs/day11.txt Normal file

File diff suppressed because one or more lines are too long

View file

@ -23,6 +23,7 @@ library:
- Day08
- Day09
- Day10
- Day11
dependencies:
- base >=4.7 && <5
- protolude

99
src/Day11.hs Normal file
View file

@ -0,0 +1,99 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-|
description:
--- Day 11: Hex Ed ---
Crossing the bridge, you've barely reached the other side of the stream when a
program comes up to you, clearly in distress. "It's my child process," she says,
"he's gotten lost in an infinite grid!"
Fortunately for her, you have plenty of experience with infinite grids.
Unfortunately for you, it's a hex grid.
The hexagons ("hexes") in this grid are aligned such that adjacent hexes can be
found to the north, northeast, southeast, south, southwest, and northwest:
\ n /
nw +--+ ne
/ \
-+ +-
\ /
sw +--+ se
/ s \
You have the path the child process took. Starting where he started, you need to
determine the fewest number of steps required to reach him. (A "step" means to
move from the hex you are in to any adjacent hex.)
For example:
- ne,ne,ne is 3 steps away.
- ne,ne,sw,sw is 0 steps away (back where you started).
- ne,ne,s,s is 2 steps away (se,se).
- se,sw,se,sw,sw is 3 steps away (s,s,sw).
--- Part Two ---
How many steps away is the furthest he ever got from his starting position?
|-}
module Day11 where
import Protolude
import qualified Data.Text as T
import Data.List (scanl',last)
data Move = NW | N | NE | SE | S | SW deriving (Show, Eq, Ord)
parseInput :: IO [Move]
parseInput = parseTxt <$> readFile "inputs/day11.txt"
parseTxt :: Text -> [Move]
parseTxt str = str & T.strip & T.splitOn "," & map strToMove
where
strToMove "n" = N
strToMove "nw" = NW
strToMove "ne" = NE
strToMove "s" = S
strToMove "sw" = SW
strToMove "se" = SE
data Coord = Coord Int Int Int deriving (Show, Eq, Ord)
direction :: Move -> Coord
direction N = Coord 0 1 (-1)
direction S = Coord 0 (-1) 1
direction NE = Coord 1 0 (-1)
direction SW = Coord (-1) 0 1
direction NW = Coord (-1) 1 0
direction SE = Coord 1 (-1) 0
sumCoord :: Coord -> Coord -> Coord
sumCoord (Coord x1 y1 z1) (Coord x2 y2 z2) =
Coord (x1 + x2) (y1 + y2) (z1 + z2)
origin :: Coord
origin = Coord 0 0 0
dist :: Coord -> Int
dist (Coord x1 y1 z1) =
(abs x1 + abs y1 + abs z1) `div` 2
solution1 :: [Move] -> Int
solution1 moves =
map direction moves
& foldl' sumCoord origin
& dist
solution2 :: [Move] -> Int
solution2 moves =
map direction moves
& scanl' sumCoord origin
& map dist
& maximum

View file

@ -11,6 +11,7 @@ import qualified Day06
import qualified Day07
import qualified Day08
import qualified Day10
import qualified Day11
main :: IO ()
@ -93,4 +94,16 @@ main = defaultMain $
, testCase "solution 2 1,2,4" $
Day10.solution2 "1,2,4" @?= "63960835bcdc130f0b66d7ff4f6a5a8e"
]
, 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
]
]
]