--- /dev/null
+-- Writeup at https://work.njae.me.uk/2024/12/13/advent-of-code-2024-day-13/
+
+import AoC
+import Data.Text (Text)
+import qualified Data.Text.IO as TIO
+import Data.Attoparsec.Text
+-- import Control.Applicative
+import Data.Maybe
+import Data.Ratio
+import Linear
+
+type Position = V2 Int -- x, y
+
+data Machine = Machine { buttonA :: Position
+ , buttonB :: Position
+ , prize :: Position
+ }
+ deriving (Show, Eq, Ord)
+
+prizeOffset :: Int
+prizeOffset = 10000000000000
+
+main :: IO ()
+main =
+ do dataFileName <- getDataFileName
+ text <- TIO.readFile dataFileName
+ let machines = successfulParse text
+ let machines' = fmap extendPrize machines
+ -- print machines
+ -- print $ filter isCollinear machines
+ -- print $ part1 machines
+ print $ part2 machines
+ print $ part2 machines'
+
+part2 :: [Machine] -> Int
+-- part1 machines = sum $ catMaybes $ fmap leastCost $ fmap findPresses machines
+part2 = sum . fmap (\(a, b) -> 3 * a + b) . catMaybes . fmap findABPresses
+
+extendPrize :: Machine -> Machine
+extendPrize m = m { prize=(m.prize ^+^ (V2 prizeOffset prizeOffset))}
+
+-- leastCost :: [(Int, Int)] -> Maybe Int
+-- leastCost [] = Nothing
+-- leastCost ps = Just $ minimum $ fmap (\(a, b) -> 3 * a + b) ps
+
+-- findPresses :: Machine -> [(Int, Int)]
+-- findPresses m = catMaybes [ findBPresses m a | a <- [0..100] ]
+
+-- findBPresses :: Machine -> Int -> Maybe (Int, Int)
+-- findBPresses (Machine {..}) a
+-- | nx == ny && mx == 0 && my == 0 = Just (a, nx)
+-- | otherwise = Nothing
+-- where aPos = a *^ buttonA
+-- V2 dx dy = prize - aPos
+-- V2 bx by = buttonB
+-- (nx, mx) = dx `divMod` bx
+-- (ny, my) = dy `divMod` by
+
+findABPresses :: Machine -> Maybe (Int, Int)
+findABPresses m@(Machine {..})
+ | denominator na == 1 && denominator nb == 1 =
+ Just (fromInteger $ numerator na, fromInteger $ numerator nb)
+ | otherwise = Nothing
+ where
+ p = intersection m
+ V2 dbx _dby = (enRat prize) ^-^ p
+ V2 px _py = p
+ V2 ax _ay = enRat buttonA
+ V2 bx _by = enRat buttonB
+ na = px / ax
+ nb = dbx / bx
+ enRat :: Position -> V2 Rational
+ enRat (V2 s t) = V2 (fromIntegral s) (fromIntegral t)
+
+-- using formula from https://en.wikipedia.org/wiki/Line%E2%80%93line_intersection#Given_two_points_on_each_line
+-- treating L1 being defined by origin and buttonA, L2 by buttonB and prize
+intersection :: Machine -> V2 Rational
+intersection (Machine {..}) = V2 px py
+ -- | denom == 0 = Nothing
+ -- | otherwise = Just (V2 px py)
+ where V2 x2 y2 = buttonA
+ V2 x4 y4 = prize
+ V2 x3 y3 = prize ^-^ buttonB
+ denom = fromIntegral (-x2 * (y3 - y4) - (-y2) * (x3 - x4))
+ px = fromIntegral (-1 * (-x2) * (x3 * y4 - y3 * x4) ) / denom
+ py = fromIntegral (-1 * (-y2) * (x3 * y4 - y3 * x4) ) / denom
+
+-- isCollinear :: Machine -> Bool
+-- isCollinear (Machine {..}) = slope buttonA == slope buttonB
+-- where
+-- slope :: Position -> Rational
+-- slope (V2 x y) = (fromIntegral y) / (fromIntegral x)
+
+-- parse the input file
+
+buttonAP, buttonBP, prizeP :: Parser Position
+machineP :: Parser Machine
+machinesP :: Parser [Machine]
+
+buttonAP = V2 <$> ("Button A: X" *> signed decimal) <* ", Y"
+ <*> signed decimal <* endOfLine
+buttonBP = V2 <$> ("Button B: X" *> signed decimal) <* ", Y"
+ <*> signed decimal <* endOfLine
+prizeP = V2 <$> ("Prize: X=" *> decimal) <* ", Y="
+ <*> decimal
+
+machineP = Machine <$> buttonAP <*> buttonBP <*> prizeP
+machinesP = machineP `sepBy` (endOfLine <* endOfLine)
+
+successfulParse :: Text -> [Machine]
+successfulParse input =
+ case parseOnly machinesP input of
+ Left _err -> [] -- TIO.putStr $ T.pack $ parseErrorPretty err
+ Right machines -> machines
+