--- /dev/null
+<!DOCTYPE html>
+<html lang="en-us">
+<head>
+<meta charset="utf-8"/>
+<title>Day 6 - Advent of Code 2018</title>
+<!--[if lt IE 9]><script src="/static/html5.js"></script><![endif]-->
+<link href='//fonts.googleapis.com/css?family=Source+Code+Pro:300&subset=latin,latin-ext' rel='stylesheet' type='text/css'>
+<link rel="stylesheet" type="text/css" href="/static/style.css?17"/>
+<link rel="stylesheet alternate" type="text/css" href="/static/highcontrast.css?0" title="High Contrast"/>
+<link rel="shortcut icon" href="/favicon.png"/>
+</head><!--
+
+
+
+
+Oh, hello! Funny seeing you here.
+
+I appreciate your enthusiasm, but you aren't going to find much down here.
+There certainly aren't clues to any of the puzzles. The best surprises don't
+even appear in the source until you unlock them for real.
+
+Please be careful with automated requests; I'm not Google, and I can only take
+so much traffic. Please be considerate so that everyone gets to play.
+
+If you're curious about how Advent of Code works, it's running on some custom
+Perl code. Other than a few integrations (auth, analytics, ads, social media),
+I built the whole thing myself, including the design, animations, prose, and
+all of the puzzles.
+
+The puzzles are most of the work; the easiest ones take 3-4 hours each, but the
+harder ones take 6-8 hours, and a few even longer than that. A lot of effort
+went into building this thing - I hope you're enjoying playing it as much as I
+enjoyed making it for you!
+
+If you'd like to hang out, I'm @ericwastl on Twitter.
+
+- Eric Wastl
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+-->
+<body>
+<header><div><h1 class="title-global"><a href="/">Advent of Code</a></h1><nav><ul><li><a href="/2018/about">[About]</a></li><li><a href="/2018/events">[Events]</a></li><li><a href="https://teespring.com/adventofcode" target="_blank">[Shop]</a></li><li><a href="/2018/settings">[Settings]</a></li><li><a href="/2018/auth/logout">[Log Out]</a></li></ul></nav><div class="user">Neil Smith <a href="/2018/support" class="supporter-badge" title="Advent of Code Supporter">(AoC++)</a> <span class="star-count">12*</span></div></div><div><h1 class="title-event"> <span class="title-event-wrap"><y></span><a href="/2018">2018</a><span class="title-event-wrap"></y></span></h1><nav><ul><li><a href="/2018">[Calendar]</a></li><li><a href="/2018/support">[AoC++]</a></li><li><a href="/2018/sponsors">[Sponsors]</a></li><li><a href="/2018/leaderboard">[Leaderboard]</a></li><li><a href="/2018/stats">[Stats]</a></li></ul></nav></div></header>
+
+<div id="sidebar">
+<div id="sponsor"><div class="quiet">Our <a href="/2018/sponsors">sponsors</a> help make Advent of Code possible:</div><div class="sponsor"><a href="https://rainway.io/" target="_blank" onclick="if(ga)ga('send','event','sponsor','click',this.href);" rel="noopener">Rainway</a> - Play all your favorite PC games anytime, anywhere, across a variety of different devices.</div></div>
+</div><!--/sidebar-->
+
+<main>
+<article class="day-desc"><h2>--- Day 6: Chronal Coordinates ---</h2><p>The device on your wrist beeps several times, and once again you feel like you're falling.</p>
+<p>"<span title="Why is the situation always critical? Why can't the situation just be boring for once?">Situation critical</span>," the device announces. "Destination indeterminate. Chronal interference detected. Please specify new target coordinates."</p>
+<p>The device then produces a list of coordinates (your puzzle input). Are they places it thinks are safe or dangerous? It recommends you check manual page 729. The Elves did not give you a manual.</p>
+<p><em>If they're dangerous,</em> maybe you can minimize the danger by finding the coordinate that gives the largest distance from the other points.</p>
+<p>Using only the <a href="https://en.wikipedia.org/wiki/Taxicab_geometry">Manhattan distance</a>, determine the <em>area</em> around each coordinate by counting the number of <a href="https://en.wikipedia.org/wiki/Integer">integer</a> X,Y locations that are <em>closest</em> to that coordinate (and aren't <em>tied in distance</em> to any other coordinate).</p>
+<p>Your goal is to find the size of the <em>largest area</em> that isn't infinite. For example, consider the following list of coordinates:</p>
+<pre><code>1, 1
+1, 6
+8, 3
+3, 4
+5, 5
+8, 9
+</code></pre>
+<p>If we name these coordinates <code>A</code> through <code>F</code>, we can draw them on a grid, putting <code>0,0</code> at the top left:</p>
+<pre><code>..........
+.A........
+..........
+........C.
+...D......
+.....E....
+.B........
+..........
+..........
+........F.
+</code></pre>
+<p>This view is partial - the actual grid extends infinitely in all directions. Using the Manhattan distance, each location's closest coordinate can be determined, shown here in lowercase:</p>
+<pre><code>aaaaa.cccc
+a<em>A</em>aaa.cccc
+aaaddecccc
+aadddecc<em>C</em>c
+..d<em>D</em>deeccc
+bb.de<em>E</em>eecc
+b<em>B</em>b.eeee..
+bbb.eeefff
+bbb.eeffff
+bbb.ffff<em>F</em>f
+</code></pre>
+<p>Locations shown as <code>.</code> are equally far from two or more coordinates, and so they don't count as being closest to any.</p>
+<p>In this example, the areas of coordinates A, B, C, and F are infinite - while not shown here, their areas extend forever outside the visible grid. However, the areas of coordinates D and E are finite: D is closest to 9 locations, and E is closest to 17 (both including the coordinate's location itself). Therefore, in this example, the size of the largest area is <em>17</em>.</p>
+<p><em>What is the size of the largest area</em> that isn't infinite?</p>
+</article>
+<p>Your puzzle answer was <code>3006</code>.</p><article class="day-desc"><h2 id="part2">--- Part Two ---</h2><p>On the other hand, <em>if the coordinates are safe</em>, maybe the best you can do is try to find a <em>region</em> near as many coordinates as possible.</p>
+<p>For example, suppose you want the sum of the <a href="https://en.wikipedia.org/wiki/Taxicab_geometry">Manhattan distance</a> to all of the coordinates to be <em>less than 32</em>. For each location, add up the distances to all of the given coordinates; if the total of those distances is less than 32, that location is within the desired region. Using the same coordinates as above, the resulting region looks like this:</p>
+<pre><code>..........
+.A........
+..........
+...#<em>#</em>#..C.
+..#D###...
+..###E#...
+.B.###....
+..........
+..........
+........F.
+</code></pre>
+<p>In particular, consider the highlighted location <code>4,3</code> located at the top middle of the region. Its calculation is as follows, where <code>abs()</code> is the <a href="https://en.wikipedia.org/wiki/Absolute_value">absolute value</a> function:</p>
+<ul>
+<li>Distance to coordinate A: <code>abs(4-1) + abs(3-1) = 5</code></li>
+<li>Distance to coordinate B: <code>abs(4-1) + abs(3-6) = 6</code></li>
+<li>Distance to coordinate C: <code>abs(4-8) + abs(3-3) = 4</code></li>
+<li>Distance to coordinate D: <code>abs(4-3) + abs(3-4) = 2</code></li>
+<li>Distance to coordinate E: <code>abs(4-5) + abs(3-5) = 3</code></li>
+<li>Distance to coordinate F: <code>abs(4-8) + abs(3-9) = 10</code></li>
+<li>Total distance: <code>5 + 6 + 4 + 2 + 3 + 10 = 30</code></li>
+</ul>
+<p>Because the total distance to all coordinates (<code>30</code>) is less than 32, the location is <em>within</em> the region.</p>
+<p>This region, which also includes coordinates D and E, has a total size of <em>16</em>.</p>
+<p>Your actual region will need to be much larger than this example, though, instead including all locations with a total distance of less than <em>10000</em>.</p>
+<p><em>What is the size of the region containing all locations which have a total distance to all given coordinates of less than 10000?</em></p>
+</article>
+<p>Your puzzle answer was <code>42998</code>.</p><p class="day-success">Both parts of this puzzle are complete! They provide two gold stars: **</p>
+<p>At this point, you should <a href="/2018">return to your advent calendar</a> and try another puzzle.</p>
+<p>If you still want to see it, you can <a href="6/input" target="_blank">get your puzzle input</a>.</p>
+<p>You can also <span class="share">[Share<span class="share-content">on
+ <a href="https://twitter.com/intent/tweet?text=I%27ve+completed+%22Chronal+Coordinates%22+%2D+Day+6+%2D+Advent+of+Code+2018&url=https%3A%2F%2Fadventofcode%2Ecom%2F2018%2Fday%2F6&related=ericwastl&hashtags=AdventOfCode" target="_blank">Twitter</a>
+ <a href="http://www.reddit.com/submit?url=https%3A%2F%2Fadventofcode%2Ecom%2F2018%2Fday%2F6&title=I%27ve+completed+%22Chronal+Coordinates%22+%2D+Day+6+%2D+Advent+of+Code+2018" target="_blank">Reddit</a
+></span>]</span> this puzzle.</p>
+</main>
+
+<!-- ga -->
+<script>
+(function(i,s,o,g,r,a,m){i['GoogleAnalyticsObject']=r;i[r]=i[r]||function(){
+(i[r].q=i[r].q||[]).push(arguments)},i[r].l=1*new Date();a=s.createElement(o),
+m=s.getElementsByTagName(o)[0];a.async=1;a.src=g;m.parentNode.insertBefore(a,m)
+})(window,document,'script','//www.google-analytics.com/analytics.js','ga');
+ga('create', 'UA-69522494-1', 'auto');
+ga('send', 'pageview');
+</script>
+<!-- /ga -->
+</body>
+</html>
\ No newline at end of file
--- /dev/null
+{-# LANGUAGE OverloadedStrings #-}
+
+import Data.List
+
+import Data.Text (Text)
+import qualified Data.Text.IO as TIO
+
+import Data.Void (Void)
+
+import Text.Megaparsec
+import Text.Megaparsec.Char
+import qualified Text.Megaparsec.Char.Lexer as L
+import qualified Control.Applicative as CA
+
+import qualified Data.Map.Strict as M
+
+type Coord = (Integer, Integer) -- x, y
+type Bounds = (Integer, Integer, Integer, Integer)
+type Region = M.Map Coord Int
+
+main :: IO ()
+main = do
+ text <- TIO.readFile "data/advent06.txt"
+ let coords = successfulParse text
+ let boundingBox = findBounds coords
+ print $ length coords
+ print boundingBox
+ print $ part1 coords boundingBox
+ print $ part2 coords boundingBox
+ -- print $ part1 activity
+ -- print $ part2 activity
+
+
+part1 coords bounds = largestRegion $ regionSizes $ finite edgeLabels regions
+ where regions = findRegions coords bounds
+ edgeLabels = infinite regions bounds
+
+part2 coords bounds = M.size $ M.filter (< 10000) $ safeCells coords bounds
+
+findRegions :: [Coord] -> Bounds -> Region
+findRegions coords (minX, maxX, minY, maxY) = M.fromList labelledCells
+ where cells = [(x, y) | x <- [minX .. maxX], y <- [minY .. maxY] ]
+ starts = zip [1..] coords
+ labelledCells = map (\c -> (c, nearestStart 0 c starts)) cells
+
+nearestStart :: Int -> Coord -> [(Int, Coord)] -> Int
+nearestStart tieLabel cell starts = nearestLabel
+ where distances = sort $ map (\(l, s) -> (distance s cell , l)) starts
+ nearestLabel = if fst (distances!!0) == fst (distances!!1)
+ then tieLabel
+ else snd (distances!!0)
+
+
+safeCells :: [Coord] -> Bounds -> Region
+safeCells coords (minX, maxX, minY, maxY) = M.fromList distanceCells
+ where cells = [(x, y) | x <- [minX .. maxX], y <- [minY .. maxY] ]
+ distanceCells = map (\c -> (c, fromIntegral $ sumDistance c coords) ) cells
+
+
+sumDistance :: Coord -> [Coord] -> Integer
+sumDistance here others = sum $ map (\c -> distance here c) others
+
+
+infinite :: Region -> Bounds -> [Int]
+infinite regions (minX, maxX, minY, maxY) = nub $ sort $ M.elems $ M.filterWithKey onEdge regions
+ where onEdge (x, y) _ = (x == minX) || (x == maxX) || (y == minY) || (y == maxY)
+
+finite :: [Int] -> Region -> Region
+finite excluded regions = M.filter (\r -> r `notElem` excludedTied) regions
+ where excludedTied = (0:excluded)
+
+
+regionSizes :: Region -> [(Int, Int)]
+regionSizes regions = map (\g -> (g!!0, length g)) $ group $ sort $ M.elems regions
+
+
+largestRegion :: [(Int, Int)] -> Int
+largestRegion = maximum . map snd
+
+
+findBounds :: [Coord] -> (Integer, Integer, Integer, Integer)
+findBounds coords = ( minX - (maxY - minY) -- small x edge
+ , maxX + (maxY - minY) -- large x edge
+ , minY - (maxX - minX) -- small x edge
+ , maxY + (maxX - minX) -- large y edge
+ )
+ where maxX = maximum $ map fst coords
+ minX = minimum $ map fst coords
+ maxY = maximum $ map snd coords
+ minY = minimum $ map snd coords
+
+-- Manhattan distance
+distance :: Coord -> Coord -> Integer
+distance (x1, y1) (x2, y2) = (abs (x1 - x2)) + (abs (y1 - y2))
+
+
+-- Parse the input file
+
+type Parser = Parsec Void Text
+
+sc :: Parser ()
+sc = L.space (skipSome spaceChar) CA.empty CA.empty
+-- sc = L.space (skipSome (char ' ')) CA.empty CA.empty
+
+lexeme = L.lexeme sc
+integer = lexeme L.decimal
+symb = L.symbol sc
+
+commaP = symb ","
+
+
+coordFileP = many coordP
+coordP = (,) <$> integer <* commaP <*> integer
+
+successfulParse :: Text -> [Coord]
+successfulParse input =
+ case parse coordFileP "input" input of
+ Left _error -> [] -- TIO.putStr $ T.pack $ parseErrorPretty err
+ Right coords -> coords
\ No newline at end of file