Files
AOC22/src/Days/Day10.hs
2022-12-12 18:08:06 +01:00

46 lines
1.2 KiB
Haskell

module Days.Day10 where
import AOCUtil
import Data.Char
import Data.List
import GHC.Utils.Misc
runA :: IO ()
runA = interactF "data/day10.txt" (solve)
runB :: IO ()
runB = interactF "data/day10.txt" (solveB)
solve :: String -> String
solve = show . sum . map score . zip [1 ..] . scanl applyInstruction 1 . cycleCorrection . map parseInstruction . lines
solveB :: String -> String
solveB = unlines . chunkList 40 . map getPixel . zip [0 ..] . scanl applyInstruction 1 . cycleCorrection . map parseInstruction . lines
data Instruction = Noop | Add Int
parseInstruction :: String -> Instruction
parseInstruction s
| isPrefixOf "noop" s = Noop
| isPrefixOf "addx" s = Add . read . last . words $ s
| otherwise = error "bad instruction"
cycleCorrection :: [Instruction] -> [Instruction]
cycleCorrection = concatMap duplicateI
duplicateI :: Instruction -> [Instruction]
duplicateI Noop = [Noop]
duplicateI (Add x) = [Noop, Add x]
applyInstruction :: Int -> Instruction -> Int
applyInstruction i Noop = i
applyInstruction i (Add x) = i + x
score :: (Int, Int) -> Int
score (i, v)
| i `elem` [20, 60, 100, 140, 180, 220] = i * v
| otherwise = 0
getPixel :: (Int, Int) -> Char
getPixel (i, v) = if abs ((i `mod` 40) - v) <= 1 then '#' else '.'