1
0
Fork 0

Day 25git status!

This commit is contained in:
Jonathan Chan 2018-12-24 22:12:58 -08:00
parent 270ef6c664
commit 3190c4b053
4 changed files with 1413 additions and 4 deletions

View File

@ -36,4 +36,4 @@ Now located in this repository's wiki.
| 22 | 23 |
| 23 | 128 |
| 24 | ~ 2 |
| 25 | |
| 25 | ~ 1 |

View File

@ -30,4 +30,4 @@ import qualified Day24
import qualified Day25
main :: IO ()
main = Day24.main
main = Day25.main

1378
input/25.txt Normal file

File diff suppressed because it is too large Load Diff

View File

@ -1,6 +1,37 @@
{-# LANGUAGE ViewPatterns #-}
module Day25 (main) where
import Prelude hiding (null)
import Data.Foldable (foldl')
import Data.Set (Set, fromList, null, empty, insert, deleteFindMin, partition, union)
type Point = (Int, Int, Int, Int)
parse :: String -> Point
parse str = read $ "(" ++ str ++ ")"
manhattan :: Point -> Point -> Int
manhattan (t1, x1, y1, z1) (t2, x2, y2, z2) = abs (t2 - t1) + abs (x2 - x1) + abs (y2 - y1) + abs (z2 - z1)
-- constellation :: starting point -> points -> (points in same constellation, points not in same constellation)
constellation :: Point -> Set Point -> (Set Point, Set Point)
constellation p ps =
let (near, far) = partition ((<= 3) . manhattan p) ps
(same, diff) = foldl' (\(n, f) p -> let (s, d) = constellation p f in (union n s, d)) (empty, far) near
in (insert p $ union same near, diff)
constellations :: Set Point -> [Set Point] -> [Set Point]
constellations (null -> True) cs = cs
constellations points cs =
let (p, ps) = deleteFindMin points
(same, diff) = constellation p ps
in constellations diff (same:cs)
part1 :: Set Point -> Int
part1 points = length $ constellations points []
main :: IO ()
main = do
input <- readFile "input/25.txt"
print input
input <- fromList . map parse . lines <$> readFile "input/25.txt"
print $ part1 input