Removed some trace prints
[advent-of-code-18.git] / src / advent06 / advent06.hs
1 {-# LANGUAGE OverloadedStrings #-}
2
3 import Data.List
4
5 import Data.Text (Text)
6 import qualified Data.Text.IO as TIO
7
8 import Data.Void (Void)
9
10 import Text.Megaparsec
11 import Text.Megaparsec.Char
12 import qualified Text.Megaparsec.Char.Lexer as L
13 import qualified Control.Applicative as CA
14
15 import qualified Data.Map.Strict as M
16
17 type Coord = (Integer, Integer) -- x, y
18 type Bounds = (Integer, Integer, Integer, Integer) -- minX, maxX, minY, maxY
19 type Region = M.Map Coord Int
20
21 main :: IO ()
22 main = do
23 text <- TIO.readFile "data/advent06.txt"
24 let coords = successfulParse text
25 let boundingBox = findBounds coords
26 print $ part1 coords boundingBox
27 print $ part2 coords boundingBox
28
29
30 part1 coords bounds = largestRegion $ regionSizes $ finite edgeLabels regions
31 where regions = findRegions coords bounds
32 edgeLabels = infinite regions bounds
33
34 part2 coords bounds = M.size $ M.filter (< 10000) $ safeCells coords bounds
35
36 findRegions :: [Coord] -> Bounds -> Region
37 findRegions coords (minX, maxX, minY, maxY) = M.fromList labelledCells
38 where cells = [(x, y) | x <- [minX .. maxX], y <- [minY .. maxY] ]
39 starts = zip [1..] coords
40 labelledCells = map (\c -> (c, nearestStart 0 c starts)) cells
41
42 nearestStart :: Int -> Coord -> [(Int, Coord)] -> Int
43 nearestStart tieLabel cell starts = nearestLabel
44 where distances = sort $ map (\(l, s) -> (distance s cell , l)) starts
45 nearestLabel = if fst (distances!!0) == fst (distances!!1)
46 then tieLabel
47 else snd (distances!!0)
48
49 safeCells :: [Coord] -> Bounds -> Region
50 safeCells coords (minX, maxX, minY, maxY) = M.fromList distanceCells
51 where cells = [(x, y) | x <- [minX .. maxX], y <- [minY .. maxY] ]
52 distanceCells = map (\c -> (c, fromIntegral $ sumDistance c coords) ) cells
53
54 sumDistance :: Coord -> [Coord] -> Integer
55 sumDistance here others = sum $ map (\c -> distance here c) others
56
57 infinite :: Region -> Bounds -> [Int]
58 infinite regions (minX, maxX, minY, maxY) = nub $ sort $ M.elems $ M.filterWithKey onEdge regions
59 where onEdge (x, y) _ = (x == minX) || (x == maxX) || (y == minY) || (y == maxY)
60
61 finite :: [Int] -> Region -> Region
62 finite excluded regions = M.filter (\r -> r `notElem` excludedTied) regions
63 where excludedTied = (0:excluded)
64
65 regionSizes :: Region -> [(Int, Int)]
66 regionSizes regions = map (\g -> (g!!0, length g)) $ group $ sort $ M.elems regions
67
68 largestRegion :: [(Int, Int)] -> Int
69 largestRegion = maximum . map snd
70
71
72 findBounds :: [Coord] -> (Integer, Integer, Integer, Integer)
73 findBounds coords = ( minX - (maxY - minY) `div` 2 -- small x edge
74 , maxX + (maxY - minY) `div` 2 -- large x edge
75 , minY - (maxX - minX) `div` 2-- small x edge
76 , maxY + (maxX - minX) `div` 2 -- large y edge
77 )
78 where maxX = maximum $ map fst coords
79 minX = minimum $ map fst coords
80 maxY = maximum $ map snd coords
81 minY = minimum $ map snd coords
82
83 -- Manhattan distance
84 distance :: Coord -> Coord -> Integer
85 distance (x1, y1) (x2, y2) = (abs (x1 - x2)) + (abs (y1 - y2))
86
87
88 -- Parse the input file
89
90 type Parser = Parsec Void Text
91
92 sc :: Parser ()
93 sc = L.space (skipSome spaceChar) CA.empty CA.empty
94
95 lexeme = L.lexeme sc
96 integer = lexeme L.decimal
97 symb = L.symbol sc
98
99 commaP = symb ","
100
101 coordFileP = many coordP
102 coordP = (,) <$> integer <* commaP <*> integer
103
104 successfulParse :: Text -> [Coord]
105 successfulParse input =
106 case parse coordFileP "input" input of
107 Left _error -> [] -- TIO.putStr $ T.pack $ parseErrorPretty err
108 Right coords -> coords