summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--2019/3.hs15
1 files changed, 15 insertions, 0 deletions
diff --git a/2019/3.hs b/2019/3.hs
index 7f0180a..b0f8e71 100644
--- a/2019/3.hs
+++ b/2019/3.hs
@@ -2,6 +2,7 @@ module Main where
import Data.Char
import Data.List
+import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import Input
@@ -48,8 +49,22 @@ points (Seg pt dir n) =
manhattan :: Pt -> Int
manhattan (Pt x y) = abs x + abs y
+data Hit = Hit {hitPt :: Pt, hitIdx :: Int} deriving (Show)
+instance Eq Hit where Hit p _ == Hit q _ = p == q
+instance Ord Hit where compare (Hit p _) (Hit q _) = compare p q
+
+points2 :: Int -> [Seg] -> [Hit]
+points2 _ [] = []
+points2 start (Seg pt dir n : segs) =
+ let delta = direction dir
+ in [Hit (add pt (scale k delta)) (start + k) | k <- [1..n]] ++ points2 (start + n) segs
+
main :: IO ()
main = do
ls <- map (process (Pt 0 0) . parse) <$> getInput 3
let pts = Set.toList (foldl1 Set.intersection (map (Set.fromList . concatMap points) ls))
print (manhattan (head (sortOn manhattan pts)))
+
+ let idxMap1 = Map.fromList . reverse $ [(hitPt h, hitIdx h) | h <- points2 0 (ls !! 0)]
+ idxMap2 = Map.fromList . reverse $ [(hitPt h, hitIdx h) | h <- points2 0 (ls !! 1)]
+ print $ minimum (zipWith (+) (map (idxMap1 Map.!) pts) (map (idxMap2 Map.!) pts))