module Main where import Text.ParserCombinators.Parsec import Data.Map.Strict (Map, (!)) import qualified Data.Map.Strict as Map import Data.Char (isDigit, isHexDigit) import Utils requiredFields = [ "byr" , "iyr" , "eyr" , "hgt" , "hcl" , "ecl" , "pid" ] eyeColors = ["amb", "blu", "brn", "gry", "grn", "hzl", "oth"] block = cell `sepBy` oneOf " \n" cell = do tag <- many lower char ':' rest <- many (alphaNum <|> char '#') return (tag, rest) parseInput :: String -> Either ParseError (Map String String) parseInput s = Map.fromList <$> parse block "input" s doCheck :: Map String String -> Bool doCheck ls = all ((== True) . flip Map.member ls) requiredFields validByr s = bet (read s :: Int) (1920, 2002) validIyr s = bet (read s :: Int) (2010, 2020) validEyr s = bet (read s :: Int) (2020, 2030) validEcl = flip elem eyeColors validPid s = length s == 9 && all isDigit s validHcl ('#':rest) = length rest == 6 && all isHexDigit rest validHcl _ = False validHgt s = let value = takeWhile isDigit s unit = dropWhile isDigit s height = (read value :: Int, unit) in case height of (v, "cm") -> bet v (150, 193) (v, "in") -> bet v (59, 76) _ -> False doValidate :: Map String String -> Bool doValidate map = all ((== True) . (\(s, v) -> v $ map ! s)) ls where ls = [ ("byr", validByr) , ("iyr", validIyr) , ("eyr", validEyr) , ("hgt", validHgt) , ("hcl", validHcl) , ("ecl", validEcl) , ("pid", validPid) ] parseLines :: [String] -> [String] parseLines allLines = unwords first : next where (first, rest) = break null allLines next = if null rest then [] else parseLines (tail rest) main :: IO () main = do n <- parseLines . lines <$> readFile "input/04" let blocks = map (right . parseInput) n {- part 1 -} print $ length $ filter doCheck blocks {- part 2 -} print $ length $ filter (doCheck &+ doValidate) blocks