Compare commits

...

2 commits

Author SHA1 Message Date
kale 71c6797d81
feat(day2): Fuck it we ball 2024-12-04 00:04:53 +01:00
kale 45c9a200e2
feat(day2): Follow the same logic for part 2 2024-12-03 22:17:28 +01:00

View file

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