A 2022/15.example => 2022/15.example +14 -0
@@ 0,0 1,14 @@
+Sensor at x=2, y=18: closest beacon is at x=-2, y=15
+Sensor at x=9, y=16: closest beacon is at x=10, y=16
+Sensor at x=13, y=2: closest beacon is at x=15, y=3
+Sensor at x=12, y=14: closest beacon is at x=10, y=16
+Sensor at x=10, y=20: closest beacon is at x=10, y=16
+Sensor at x=14, y=17: closest beacon is at x=10, y=16
+Sensor at x=8, y=7: closest beacon is at x=2, y=10
+Sensor at x=2, y=0: closest beacon is at x=2, y=10
+Sensor at x=0, y=11: closest beacon is at x=2, y=10
+Sensor at x=20, y=14: closest beacon is at x=25, y=17
+Sensor at x=17, y=20: closest beacon is at x=21, y=22
+Sensor at x=16, y=7: closest beacon is at x=15, y=3
+Sensor at x=14, y=3: closest beacon is at x=15, y=3
+Sensor at x=20, y=1: closest beacon is at x=15, y=3
A 2022/15.hs => 2022/15.hs +79 -0
@@ 0,0 1,79 @@
+{-# LANGUAGE BangPatterns #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE NamedFieldPuns #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+module Main where
+
+import Qulude hiding ( rotate )
+
+--import Data.Array ( (!) )
+import qualified Data.Array as Array
+import qualified Data.Either as Either
+import qualified Data.List as List
+--import Data.Array ( (!) )
+import qualified Data.Map as Map
+import qualified Data.Maybe as Maybe
+import qualified Data.Sequence as Seq
+import qualified Data.Set as Set
+
+type Point = (Int,Int)
+type Sensor = (Point, Point)
+
+type Parse = [ Sensor ]
+parser :: Parser Parse
+parser = many sensor
+ where sensor = do
+ string "Sensor at "
+ s <- point
+ string ": closest beacon is at "
+ b <- point
+ newline
+ return (s, b)
+ point = do
+ string "x="
+ x <- int
+ string ", y="
+ y <- int
+ return (x, y)
+
+dist :: Point -> Point -> Int
+dist (x0,y0) (x1,y1) = abs (x1 - x0) + abs (y1 - y0)
+
+isCovered :: Point -> Sensor -> Bool
+isCovered p (s, b) = dist s p <= dist s b
+
+bounds :: [ Sensor ] -> Maybe (Point, Point)
+bounds [] = Nothing
+bounds ((s@(x,y),b):ss) =
+ let t = dist s b in
+ let ((x0,y0), (x1,y1)) = ((x-t,y-t),(x+t,y+t)) in
+ case bounds ss of
+ Nothing -> Just ((x0,y0), (x1,y1))
+ Just ((x0',y0'), (x1',y1')) ->
+ Just ((min x0 x0', min y0 y0'), (max x1 x1', max y1 y1'))
+
+partA y ss = let Just ((x0,_),(x1,_)) = bounds ss in count [ check (x, y) | x <- [x0..x1] ]
+ where check p = or $ fmap (\s@(_,b) -> p /= b && isCovered p s) ss
+
+--partB m ss = head [ tf x y | x <- [0..m], y <- [0..m], check (x,y) ]
+ --where check p = not $ or $ fmap (\s -> (isCovered p s)) ss
+ --tf x y = x * 4000000 + y
+
+rotate a (x, y) = (x*cos a - y*sin a, x*sin a + y*cos a)
+
+partB _ ss = [ (f a b, a, b) | (a, _) <- ss, (b, _) <- ss ]
+ where pi4 = pi / 4
+ sq2 = sqrt 2 / 2
+ t (x, y) = (fromIntegral x, fromIntegral y)
+ f a b =
+ let (rax, ray) = rotate pi4 (t a) in
+ let (rbx, rby) = rotate pi4 (t b) in
+ (round $ (rax - rbx)/sq2, round $ (ray - rby)/sq2)
+
+main :: IO ()
+main = with parser $ do
+ run' "15.example" "a example" (partA 10) 26
+ --run' "15.input" "a input" (partA 2000000) 5299855
+ run "15.example" "b example" (partB 20)
+ --run "15.input" "b input" (partB 4000000)
A 2022/15.input => 2022/15.input +26 -0
@@ 0,0 1,26 @@
+Sensor at x=3772068, y=2853720: closest beacon is at x=4068389, y=2345925
+Sensor at x=78607, y=2544104: closest beacon is at x=-152196, y=4183739
+Sensor at x=3239531, y=3939220: closest beacon is at x=3568548, y=4206192
+Sensor at x=339124, y=989831: closest beacon is at x=570292, y=1048239
+Sensor at x=3957534, y=2132743: closest beacon is at x=3897332, y=2000000
+Sensor at x=1882965, y=3426126: closest beacon is at x=2580484, y=3654136
+Sensor at x=1159443, y=3861139: closest beacon is at x=2580484, y=3654136
+Sensor at x=2433461, y=287013: closest beacon is at x=2088099, y=-190228
+Sensor at x=3004122, y=3483833: closest beacon is at x=2580484, y=3654136
+Sensor at x=3571821, y=799602: closest beacon is at x=3897332, y=2000000
+Sensor at x=2376562, y=1539540: closest beacon is at x=2700909, y=2519581
+Sensor at x=785113, y=1273008: closest beacon is at x=570292, y=1048239
+Sensor at x=1990787, y=38164: closest beacon is at x=2088099, y=-190228
+Sensor at x=3993778, y=3482849: closest beacon is at x=4247709, y=3561264
+Sensor at x=3821391, y=3986080: closest beacon is at x=3568548, y=4206192
+Sensor at x=2703294, y=3999015: closest beacon is at x=2580484, y=3654136
+Sensor at x=1448314, y=2210094: closest beacon is at x=2700909, y=2519581
+Sensor at x=3351224, y=2364892: closest beacon is at x=4068389, y=2345925
+Sensor at x=196419, y=3491556: closest beacon is at x=-152196, y=4183739
+Sensor at x=175004, y=138614: closest beacon is at x=570292, y=1048239
+Sensor at x=1618460, y=806488: closest beacon is at x=570292, y=1048239
+Sensor at x=3974730, y=1940193: closest beacon is at x=3897332, y=2000000
+Sensor at x=2995314, y=2961775: closest beacon is at x=2700909, y=2519581
+Sensor at x=105378, y=1513086: closest beacon is at x=570292, y=1048239
+Sensor at x=3576958, y=3665667: closest beacon is at x=3568548, y=4206192
+Sensor at x=2712265, y=2155055: closest beacon is at x=2700909, y=2519581