From 031746bd8c349b485b4914d1788ec944b1e534a2 Mon Sep 17 00:00:00 2001 From: Akshay Date: Fri, 4 Dec 2020 14:21:24 +0530 Subject: add initial solution to day 4 --- execs/Day02.hs | 4 +-- execs/Day04.hs | 82 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 2 files changed, 84 insertions(+), 2 deletions(-) create mode 100644 execs/Day04.hs (limited to 'execs') diff --git a/execs/Day02.hs b/execs/Day02.hs index f67778b..b06b44d 100644 --- a/execs/Day02.hs +++ b/execs/Day02.hs @@ -37,5 +37,5 @@ parseLine parser line = right $ parse parser "input" line main :: IO () main = do - n <- map (fromEnum . doCheck2 . parseLine parseProp) . lines <$> readFile "input/02" - print $ sum n + n <- map (doCheck2 . parseLine parseProp) . lines <$> readFile "input/02" + print $ countElem True n diff --git a/execs/Day04.hs b/execs/Day04.hs new file mode 100644 index 0000000..04aacbb --- /dev/null +++ b/execs/Day04.hs @@ -0,0 +1,82 @@ +module Main where + +import Text.ParserCombinators.Parsec +import Text.Parsec.Char +import Data.Either +import Data.Maybe +import Control.Monad +import Data.List (sortOn) + +right (Right a) = a +fields = [ "byr" , "iyr" , "eyr" , "hgt" , "hcl" , "ecl" , "pid" ] + +block = cell `sepBy` oneOf " \n" +cell = do + tag <- many lower + char ':' + rest <- many (alphaNum <|> char '#') + return (tag, rest) + +parseInput :: String -> Either ParseError [(String, String)] +parseInput = parse block "input" + +assocGet s (l:ls) = if fst l == s + then snd l + else assocGet s ls + +doCheck :: [(String, String)] -> Bool +doCheck ls = all (isJust . flip lookup ls) fields + +checkNum lower up s = p >= lower && p <= up + where p = read s :: Int +byr = checkNum 1920 2002 +iyr = checkNum 2010 2020 +eyr = checkNum 2020 2030 + +parseHeight :: Parser (Int, String) +parseHeight = do + v <- many1 digit + unit <- choice $ map string ["cm", "in"] + return (read v, unit) +hgt s = case parse parseHeight "hgt" s of + Right (v, "cm") -> v >= 150 && v <= 193 + Right (v, "in") -> v >= 59 && v <= 76 + _ -> False + +parseColor = char '#' >> many hexDigit +hcl :: String -> Bool +hcl s = case parse parseColor "hcl" s of + Right c -> length c == 6 + Left _ -> False + + +ecl :: String -> Bool +ecl = flip elem ["amb", "blu", "brn", "gry", "grn", "hzl", "oth"] + +parsePid = replicateM 9 digit +pid :: String -> Bool +pid s = isRight $ parse parsePid "pid" s + +doValidity :: [(String, String)] -> Bool +doValidity ls = all ((== True) . ($ ls)) [ byr . assocGet "byr" + , iyr . assocGet "iyr" + , eyr . assocGet "eyr" + , hgt . assocGet "hgt" + , hcl . assocGet "hcl" + , ecl . assocGet "ecl" + , pid . assocGet "pid" + ] + +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 + print $ length $ filter (\p -> doCheck p && doValidity p) blocks + -- mapM_ print $ filter (\p -> doCheck p && doValidity p) $ map (sortOn fst) blocks + -- print $ length $ filter doCheck blocks + -- print $ length $ filter (\p -> doCheck p && doValidity p) $ map (sortOn fst) blocks -- cgit v1.2.3