summaryrefslogtreecommitdiff
path: root/2021/5.hs
diff options
context:
space:
mode:
Diffstat (limited to '2021/5.hs')
-rw-r--r--2021/5.hs29
1 files changed, 29 insertions, 0 deletions
diff --git a/2021/5.hs b/2021/5.hs
new file mode 100644
index 0000000..7ab4f3b
--- /dev/null
+++ b/2021/5.hs
@@ -0,0 +1,29 @@
+{-# LANGUAGE TupleSections #-}
+module Main where
+
+import qualified Data.Array as A
+
+import Input
+
+
+main :: IO ()
+main = do
+ let parseLine s = let [a,_,b] = words s in (parsePt a, parsePt b)
+ parsePt s = let (a,_:b) = break (== ',') s in (read a, read b) :: (Int, Int)
+ inp <- map parseLine <$> getInput 5
+ let minmax = (,) <$> minimum <*> maximum
+ (minx, maxx) = minmax (concatMap (\((a,_),(b,_)) -> [a,b]) inp)
+ (miny, maxy) = minmax (concatMap (\((_,a),(_,b)) -> [a,b]) inp)
+ let enumLine diag ((x1,y1),(x2,y2))
+ | (diag && abs (x1 - x2) == abs (y1 - y2)) || x1 == x2 || y1 == y2
+ = let dx = signum (x2 - x1)
+ dy = signum (y2 - y1)
+ in [(x1 + i * dx, y1 + i * dy)
+ | i <- [0 .. max (abs (x2 - x1)) (abs (y2 - y1))]]
+ | otherwise = []
+ bd diag = A.accumArray (+) (0::Int) ((minx, miny), (maxx, maxy))
+ [((x, y), 1)
+ | line <- inp
+ , (x, y) <- enumLine diag line]
+ print (length (filter (> 1) (A.elems (bd False))))
+ print (length (filter (> 1) (A.elems (bd True))))