This commit is contained in:
Christian
2023-09-25 12:13:13 +02:00
parent f9e3cf2f75
commit b5468d1db7
6 changed files with 511 additions and 0 deletions

57
src/Days/D13.hs Normal file
View File

@@ -0,0 +1,57 @@
module Days.D13 where
import Common
import Data.List (foldl')
import Parse
import Text.Megaparsec (between, sepBy, (<|>))
import Text.Megaparsec.Char (char, newline)
data Packet
= N Int
| L [Packet]
deriving (Show, Eq)
instance Ord Packet where
compare (N a) (N b) = compare a b
compare (L a) (L b) = compare a b
compare (N a) b = compare (L [N a]) b
compare a (N b) = compare a (L [N b])
parser :: Parser [(Packet, Packet)]
parser = sepBy packetPair newline
where
packetPair :: Parser (Packet, Packet)
packetPair = (,) <$> packet <* newline <*> packet <* newline
packet :: Parser Packet
packet =
(L <$> between (char '[') (char ']') (sepBy packet (char ',')))
<|> (N <$> number)
part1 :: [(Packet, Packet)] -> Int
part1 l = sum [idx | (idx, pair) <- zip [1 ..] l, uncurry (<) pair]
sep2 :: Packet
sep2 = L [L [N 2]]
sep6 :: Packet
sep6 = L [L [N 6]]
part2 :: [(Packet, Packet)] -> Int
part2 =
(\(acc2, acc6) -> (acc2 + 1) * (acc2 + acc6 + 2))
. foldl'
( \(acc2, acc6) p ->
( if p < sep2
then (acc2 + 1, acc6)
else
if p < sep6
then (acc2, acc6 + 1)
else (acc2, acc6)
)
)
(0, 0)
. foldl' (\acc (p1, p2) -> p1 : p2 : acc) []
day :: Day
day = parsecDay parser (definitive . part1, definitive . part2)

View File

@@ -24,6 +24,7 @@ import Days.D09 qualified as D09
import Days.D10 qualified as D10
import Days.D11 qualified as D11
import Days.D12 qualified as D12
import Days.D13 qualified as D13
import Data.ByteString.Char8 qualified as BS
import Data.Text.IO qualified as T
@@ -48,4 +49,5 @@ days =
, [D10.day]
, [D11.day]
, [D12.day]
, [D13.day]
]