aoc-2024-haskell/day2/Main.hs

59 lines
1.6 KiB
Haskell

module Main where
import System.Environment (getArgs)
import Text.Parsec (parse, many1, char, sepBy, endBy)
import Text.Parsec.Char (endOfLine)
import Text.ParserCombinators.Parsec (GenParser)
import Text.ParserCombinators.Parsec.Number (decimal)
type Report = [Level]
type Level = Int
reports :: GenParser Char st [Report]
reports = endBy report endOfLine
report :: GenParser Char st Report
report = sepBy level (many1 (char ' '))
level :: GenParser Char st Level
level = decimal
pairUp :: [a] -> [(a, a)]
pairUp (a:b:tl) = (a, b) : pairUp (b:tl)
pairUp _ = []
allIncOrDec :: Bool -> Report -> Bool
allIncOrDec dampened (a:b:tl) = if a /= b
then (if dampened then (>=) 0 else (==) 0)
$ length
$ filter (not . uncurry (if a < b then (<) else (>)))
$ pairUp
$ b:tl
else dampened && allIncOrDec False (b:tl)
allIncOrDec _ _ = True
notTooDifferent :: Bool -> Report -> Bool
notTooDifferent dampened (a:b:tl) =
let dif = abs (a - b)
in if (1 <= dif) && (dif <= 3)
then notTooDifferent dampened (b:tl)
else dampened && notTooDifferent False (b:tl)
notTooDifferent _ _ = True
solve :: Bool -> [Report] -> Int
solve dampened = length
. filter (allIncOrDec dampened)
. filter (notTooDifferent dampened)
main :: IO ()
main = do
args <- getArgs
(fp:_) <- return args
content <- readFile fp
case parse reports fp content of
Left e -> putStrLn ("Input file is incorrectly formatted : " ++ show e)
Right r -> do
putStrLn ("Solution (Part 1) : " ++ show (solve False r))
putStrLn ("Solution (Part 2) : " ++ show (solve True r))