Done day 3 part 2
[advent-of-code-19.git] / advent03 / src / advent03part1.hs
1 import Data.Text (Text)
2 import qualified Data.Text.IO as TIO
3
4 import Data.Void (Void)
5
6 import Text.Megaparsec hiding (State)
7 import Text.Megaparsec.Char
8 import qualified Text.Megaparsec.Char.Lexer as L
9 import qualified Control.Applicative as CA
10
11 import Data.List (foldl')
12 import qualified Data.Set as S
13
14 import Linear (V2(..), (^+^), (^-^), (*^), (*^))
15
16 data Direction = East | South | West | North deriving (Show, Eq)
17
18 type Location = V2 Int -- x, y
19
20 type Visited = S.Set Location
21
22 data Path = Path { _visited :: Visited
23 , _tip :: Location
24 }
25 deriving (Show, Eq)
26
27 data Segment = Segment { _direction :: Direction
28 , _steps :: Int
29 } deriving (Show, Eq)
30
31
32 main :: IO ()
33 main = do
34 text <- TIO.readFile "data/advent03.txt"
35 let segmentss = successfulParse text
36 -- print segmentss
37 -- print $ travelPath $ head segmentss
38 print $ part1 segmentss
39 -- print $ part2 machine
40
41 part1 :: [[Segment]] -> Int
42 part1 segmentss = closest $ crossovers $ travelAllPaths segmentss
43
44 closest :: Visited -> Int
45 closest points = S.findMin $ S.map manhattan points
46
47 crossovers :: [Path] -> Visited
48 crossovers travelledPaths =
49 foldl' S.intersection
50 (_visited $ head travelledPaths)
51 (map _visited $ drop 1 travelledPaths)
52
53 travelAllPaths :: [[Segment]] -> [Path]
54 travelAllPaths = map travelPath
55
56 travelPath :: [Segment] -> Path
57 travelPath segments = foldl' travelSegment path0 segments
58 where path0 = Path { _visited = S.empty, _tip = V2 0 0 }
59
60 travelSegment :: Path -> Segment -> Path
61 travelSegment path segment = path { _tip = tip', _visited = visited' }
62 where delta = facing $ _direction segment
63 distance = _steps segment
64 start = _tip path
65 visited = _visited path
66 visited' = foldl' (flip S.insert) visited $ take distance $ drop 1 $ iterate (^+^ delta) start
67 tip' = start ^+^ distance *^ delta
68
69 facing :: Direction -> Location
70 facing East = V2 1 0
71 facing South = V2 0 (-1)
72 facing West = V2 (-1) 0
73 facing North = V2 0 1
74
75
76 manhattan (V2 x y) = (abs x) + (abs y)
77
78 -- Parse the input file
79 type Parser = Parsec Void Text
80
81 sc :: Parser ()
82 sc = L.space (skipSome spaceChar) CA.empty CA.empty
83 -- sc = L.space (skipSome (char ' ')) CA.empty CA.empty
84
85 lexeme = L.lexeme sc
86 integer = lexeme L.decimal
87 -- signedInteger = L.signed sc integer
88 symb = L.symbol sc
89 comma = symb ","
90
91 wiresP = some pathP
92 pathP = segmentP `sepBy1` comma
93
94 segmentP = segmentify <$> directionP <*> integer
95 where segmentify direction steps =
96 Segment { _direction = direction, _steps = steps }
97
98
99 directionP = eP <|> sP <|> wP <|> nP
100 eP = (symb "R" *> pure East)
101 sP = (symb "D" *> pure South)
102 wP = (symb "L" *> pure West)
103 nP = (symb "U" *> pure North)
104
105
106 successfulParse :: Text -> [[Segment]]
107 successfulParse input =
108 case parse wiresP "input" input of
109 Left _err -> [] -- TIO.putStr $ T.pack $ parseErrorPretty err
110 Right wires -> wires