From df7a8ac54e22baaaf47bbddaee3eff74e2730905 Mon Sep 17 00:00:00 2001 From: Tom Smeding Date: Tue, 10 Dec 2019 21:25:10 +0100 Subject: Day 10 part 2 WIP --- 2019/10.hs | 58 +++++++++++++++++++++++++++++++++++++++++++++------------- 1 file changed, 45 insertions(+), 13 deletions(-) (limited to '2019/10.hs') diff --git a/2019/10.hs b/2019/10.hs index 5b6e09c..964e219 100644 --- a/2019/10.hs +++ b/2019/10.hs @@ -1,22 +1,54 @@ module Main where import Data.Array.Unboxed +import Data.List (maximumBy, sortBy, sortOn, groupBy) +import Data.Ord (comparing) +-- import Data.Ratio import Input main :: IO () main = do - inp <- getInput 10 - let h = length inp - w = length (head inp) - arr = listArray ((0, 0), (w-1, h-1)) (concatMap (map (== '#')) inp) + inp <- getInput 10 + let h = length inp + w = length (head inp) + arr = array ((0, 0), (w-1, h-1)) [((x, y), c == '#') | (y, row) <- zip [0..] inp, (x, c) <- zip [0..] row] :: UArray (Int, Int) Bool - asts = map fst (filter snd (assocs arr)) - sight (a,b) (x,y) = - let dx = (x - a) `div` g - dy = (y - b) `div` g - g = gcd (abs (x - a)) (abs (y - b)) - pts = [(a + i * dx, b + i * dy) | i <- [1..g-1]] - in all (not . (arr !)) pts - numVisible p = length (filter (\q -> q /= p && sight p q) asts) - print (maximum (map numVisible asts)) + asts = map fst (filter snd (assocs arr)) + sight (a,b) (x,y) = + let dx = (x - a) `div` g + dy = (y - b) `div` g + g = gcd (abs (x - a)) (abs (y - b)) + pts = [(a + i * dx, b + i * dy) | i <- [1..g-1]] + in all (not . (arr !)) pts + numVisible p = length (filter (\q -> q /= p && sight p q) asts) + -- (cent@(centx, centy), centNumVis) = maximumBy (comparing snd) (zip asts (map numVisible asts)) + (cent@(centx, centy), centNumVis) = ((8, 3), 42) + + print centNumVis + + print cent + + let -- atan2R' dy dx + -- | dy <= 0, dx < 0 = abs dy % abs dx : -inf -> 0 + -- | dy > 0, dx < 0 = abs dy % abs dx : 0 -> inf + -- | dy > 0, dx == 0 = 0 + -- | dy > 0, dx > 0 = abs dy % abs dx : inf -> 0 + -- | dy <= 0, dx > 0 = abs dy % abs dx : 0 -> -inf + -- | dy < 0, dx == 0 = 1 + -- | otherwise = undefined -- (dx, dy) == (0, 0) + threeLine (cx, cy) (a, b) (x, y) = (a - cx) * (y - cy) == (x - cx) * (b - cy) + distsq (a, b) (x, y) = (x - a) * (x - a) + (y - b) * (y - b) + otherAsts = sortOn (\(x, y) -> atan2 (fromIntegral (centx - x) :: Double) (fromIntegral (y - centy))) + (filter (/= cent) asts) + groups' = map (sortBy (comparing (distsq cent))) (groupBy (threeLine cent) otherAsts) + groups = last groups' : init groups' + zapRound l = (map head l, filter (not . null) (map tail l)) + zapped = concat (takeWhile (not . null) (map fst (tail (iterate (zapRound . snd) (undefined, groups))))) + + mapM_ print groups + print zapped + print (zapped !! 199) + + -- let (n200x, n200y) = otherAsts !! 199 + -- print (n200x * 100 + n200y) -- cgit v1.2.3-54-g00ecf