1 import Data.Text (Text)
2 import qualified Data.Text.IO as TIO
4 import Data.Void (Void)
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
11 import Data.List (foldl', foldl1')
12 import qualified Data.Set as S
14 import Linear (V2(..), (^+^), (^-^), (*^), (*^))
16 data Direction = East | South | West | North deriving (Show, Eq)
18 type Location = V2 Int -- x, y
20 type Visited = S.Set Location
22 data Path = Path { _visited :: Visited
27 data Segment = Segment { _direction :: Direction
34 text <- TIO.readFile "data/advent03.txt"
35 let segmentss = successfulParse text
37 -- print $ travelPath $ head segmentss
38 print $ part1 segmentss
39 -- print $ part2 machine
41 part1 :: [[Segment]] -> Int
42 part1 segmentss = closest $ crossovers $ travelAllPaths segmentss
44 closest :: Visited -> Int
45 closest points = S.findMin $ S.map manhattan points
47 crossovers :: [Path] -> Visited
48 crossovers travelledPaths =
49 foldl1' S.intersection $ map _visited travelledPaths
51 travelAllPaths :: [[Segment]] -> [Path]
52 travelAllPaths = map travelPath
54 travelPath :: [Segment] -> Path
55 travelPath segments = foldl' travelSegment path0 segments
56 where path0 = Path { _visited = S.empty, _tip = V2 0 0 }
58 travelSegment :: Path -> Segment -> Path
59 travelSegment path segment = path { _tip = tip', _visited = visited' }
60 where delta = facing $ _direction segment
61 distance = _steps segment
63 visited = _visited path
64 visited' = foldl' (flip S.insert) visited $ take distance $ drop 1 $ iterate (^+^ delta) start
65 tip' = start ^+^ distance *^ delta
67 facing :: Direction -> Location
69 facing South = V2 0 (-1)
70 facing West = V2 (-1) 0
74 manhattan (V2 x y) = (abs x) + (abs y)
76 -- Parse the input file
77 type Parser = Parsec Void Text
80 sc = L.space (skipSome spaceChar) CA.empty CA.empty
81 -- sc = L.space (skipSome (char ' ')) CA.empty CA.empty
84 integer = lexeme L.decimal
85 -- signedInteger = L.signed sc integer
90 pathP = segmentP `sepBy1` comma
92 segmentP = segmentify <$> directionP <*> integer
93 where segmentify direction steps =
94 Segment { _direction = direction, _steps = steps }
97 directionP = eP <|> sP <|> wP <|> nP
98 eP = (symb "R" *> pure East)
99 sP = (symb "D" *> pure South)
100 wP = (symb "L" *> pure West)
101 nP = (symb "U" *> pure North)
104 successfulParse :: Text -> [[Segment]]
105 successfulParse input =
106 case parse wiresP "input" input of
107 Left _err -> [] -- TIO.putStr $ T.pack $ parseErrorPretty err