Tweaking
[advent-of-code-17.git] / src / advent20 / advent20.hs
1 {-# LANGUAGE NegativeLiterals #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE OverloadedStrings #-}
4 {-# LANGUAGE TypeFamilies #-}
5 {-# LANGUAGE BangPatterns #-}
6
7 import Data.Text (Text)
8 import qualified Data.Text as T
9 import qualified Data.Text.IO as TIO
10
11 import Text.Megaparsec hiding (State)
12 import qualified Text.Megaparsec.Lexer as L
13 import Text.Megaparsec.Text (Parser)
14 import qualified Control.Applicative as CA
15
16 import qualified Data.Vector as V
17
18 import Data.List
19
20 import qualified Data.Set as S
21
22
23 type Vec = V.Vector Integer
24
25 data Particle = Particle
26 { position :: Vec
27 , velocity :: Vec
28 , acceleration :: Vec
29 } deriving (Show, Eq)
30
31
32 main :: IO ()
33 main = do
34 text <- TIO.readFile "data/advent20.txt"
35 let particles = successfulParse text
36 print $ part1 particles
37 print $ part2 500 particles
38
39
40 part1 :: [Particle] -> Int
41 part1 particles = head $ withMinX $ simulate particles
42
43 part2 :: Integer -> [Particle] -> Int
44 part2 n particles = length $ simulateC n particles
45
46 simulate :: [Particle] -> [Particle]
47 simulate particles =
48 if all quiescent particles && length withMinXs == 1
49 then particles
50 else simulate (map step particles)
51 where withMinXs = withMinX particles
52
53
54 simulateC :: Integer -> [Particle] -> [Particle]
55 simulateC 0 particles = particles
56 simulateC t particles = simulateC (t - 1) (map step particles')
57 where particles' = removeColliders particles
58
59
60 step :: Particle -> Particle
61 step particle = particle {position = p', velocity = v'}
62 where pv' = V.zipWith3 updatePV (position particle) (velocity particle) (acceleration particle)
63 (p', v') = V.unzip pv'
64 updatePV p v a = (p + v + a, v + a)
65
66
67 -- Checks whether a particle could ever get closer to the origin than it is now.
68 quiescent :: Particle -> Bool
69 quiescent particle = and qDimensions
70 where qDimensions = V.zipWith3 sameSigns (position particle) (velocity particle) (acceleration particle)
71 sameSigns p v a = if a == 0 && v == 0
72 then True
73 else if a == 0
74 then signum p == signum v
75 else signum p == signum v && signum v == signum a
76
77
78 withMinX particles = minX `elemIndices` absXs
79 where absXs = map pAbsX particles
80 minX = minimum absXs
81
82 pAbsX :: Particle -> Integer
83 pAbsX particle = V.foldl1' (+) $ V.map abs (position particle)
84
85
86 removeColliders particles = particles'
87 where positions = map position particles
88 duplicatePositions = S.fromList $ concat $ filter (\g -> length g > 1) $ group $ sort positions
89 particles' = filter (\p -> not (S.member (position p) duplicatePositions)) particles
90
91
92
93 sc :: Parser ()
94 sc = L.space (skipSome spaceChar) CA.empty CA.empty
95
96 lexeme = L.lexeme sc
97
98 integer = lexeme L.integer
99 signedInteger = L.signed sc integer
100
101 symbol = L.symbol sc
102 separator = symbol ", "
103 comma = symbol ","
104
105 particlesP = particleP `sepBy` space
106 particleP = particlify <$> (symbol "p=" *> vecP <* separator)
107 <*> (symbol "v=" *> vecP <* separator)
108 <*> (symbol "a=" *> vecP)
109 where particlify p v a = Particle {position = p, velocity = v, acceleration = a}
110
111
112 vecP = V.fromList <$> between (symbol "<") (symbol ">") (signedInteger `sepBy` comma)
113
114
115 successfulParse :: Text -> [Particle]
116 successfulParse input =
117 case parse particlesP "input" input of
118 Left _error -> [] -- TIO.putStr $ T.pack $ parseErrorPretty err
119 Right instructions -> instructions