feat(day2): Fuck it we ball

This commit is contained in:
kale 2024-12-04 00:04:53 +01:00
parent 45c9a200e2
commit 71c6797d81
Signed by: kalmenn
GPG key ID: F500055C44BC3834

View file

@ -2,6 +2,8 @@ module Main where
import System.Environment (getArgs) import System.Environment (getArgs)
import Control.Exception (assert)
import Text.Parsec (parse, many1, char, sepBy, endBy) import Text.Parsec (parse, many1, char, sepBy, endBy)
import Text.Parsec.Char (endOfLine) import Text.Parsec.Char (endOfLine)
import Text.ParserCombinators.Parsec (GenParser) import Text.ParserCombinators.Parsec (GenParser)
@ -23,28 +25,28 @@ pairUp :: [a] -> [(a, a)]
pairUp (a:b:tl) = (a, b) : pairUp (b:tl) pairUp (a:b:tl) = (a, b) : pairUp (b:tl)
pairUp _ = [] pairUp _ = []
allIncOrDec :: Bool -> Report -> Bool isSafe :: Report -> Bool
allIncOrDec dampened (a:b:tl) = if a /= b isSafe (a:b:tl) = a /= b && (==) 0 (
then (if dampened then (>=) 0 else (==) 0) length $ filter (not . (\(l, r) -> let
$ length dif = abs (l - r)
$ filter (not . uncurry (if a < b then (<) else (>))) cmp = if a < b then (<) else assert (b < a) (>)
in (1 <= dif) && (dif <= 3) && l `cmp` r))
$ pairUp $ pairUp
$ b:tl $ a:b:tl)
else dampened && allIncOrDec False (b:tl) isSafe _ = True
allIncOrDec _ _ = True
notTooDifferent :: Bool -> Report -> Bool with1Removed :: Report -> [Report]
notTooDifferent dampened (a:b:tl) = with1Removed (h:tl) = tl : map (h :) (with1Removed tl)
let dif = abs (a - b) with1Removed [] = []
in if (1 <= dif) && (dif <= 3)
then notTooDifferent dampened (b:tl)
else dampened && notTooDifferent False (b:tl)
notTooDifferent _ _ = True
solve :: Bool -> [Report] -> Int isKindaSafe :: Report -> Bool
solve dampened = length isKindaSafe = any isSafe . with1Removed
. filter (allIncOrDec dampened)
. filter (notTooDifferent dampened) part1 :: [Report] -> Int
part1 = length . filter isSafe
part2 :: [Report] -> Int
part2 = length . filter isKindaSafe
main :: IO () main :: IO ()
main = do main = do
@ -54,5 +56,5 @@ main = do
case parse reports fp content of case parse reports fp content of
Left e -> putStrLn ("Input file is incorrectly formatted : " ++ show e) Left e -> putStrLn ("Input file is incorrectly formatted : " ++ show e)
Right r -> do Right r -> do
putStrLn ("Solution (Part 1) : " ++ show (solve False r)) putStrLn ("Solution (Part 1) : " ++ show (part1 r))
putStrLn ("Solution (Part 2) : " ++ show (solve True r)) putStrLn ("Solution (Part 2) : " ++ show (part2 r))