diff options
author | Akshay <[email protected]> | 2020-12-04 08:51:24 +0000 |
---|---|---|
committer | Akshay <[email protected]> | 2020-12-04 08:51:24 +0000 |
commit | 031746bd8c349b485b4914d1788ec944b1e534a2 (patch) | |
tree | 187573bc58c1318d7292fac771cf5b28b98eea62 /execs | |
parent | 24dade573ba48d83265f88e3850958ff7e3d61bd (diff) |
add initial solution to day 4
Diffstat (limited to 'execs')
-rw-r--r-- | execs/Day02.hs | 4 | ||||
-rw-r--r-- | execs/Day04.hs | 82 |
2 files changed, 84 insertions, 2 deletions
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 | |||
37 | 37 | ||
38 | main :: IO () | 38 | main :: IO () |
39 | main = do | 39 | main = do |
40 | n <- map (fromEnum . doCheck2 . parseLine parseProp) . lines <$> readFile "input/02" | 40 | n <- map (doCheck2 . parseLine parseProp) . lines <$> readFile "input/02" |
41 | print $ sum n | 41 | 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 @@ | |||
1 | module Main where | ||
2 | |||
3 | import Text.ParserCombinators.Parsec | ||
4 | import Text.Parsec.Char | ||
5 | import Data.Either | ||
6 | import Data.Maybe | ||
7 | import Control.Monad | ||
8 | import Data.List (sortOn) | ||
9 | |||
10 | right (Right a) = a | ||
11 | fields = [ "byr" , "iyr" , "eyr" , "hgt" , "hcl" , "ecl" , "pid" ] | ||
12 | |||
13 | block = cell `sepBy` oneOf " \n" | ||
14 | cell = do | ||
15 | tag <- many lower | ||
16 | char ':' | ||
17 | rest <- many (alphaNum <|> char '#') | ||
18 | return (tag, rest) | ||
19 | |||
20 | parseInput :: String -> Either ParseError [(String, String)] | ||
21 | parseInput = parse block "input" | ||
22 | |||
23 | assocGet s (l:ls) = if fst l == s | ||
24 | then snd l | ||
25 | else assocGet s ls | ||
26 | |||
27 | doCheck :: [(String, String)] -> Bool | ||
28 | doCheck ls = all (isJust . flip lookup ls) fields | ||
29 | |||
30 | checkNum lower up s = p >= lower && p <= up | ||
31 | where p = read s :: Int | ||
32 | byr = checkNum 1920 2002 | ||
33 | iyr = checkNum 2010 2020 | ||
34 | eyr = checkNum 2020 2030 | ||
35 | |||
36 | parseHeight :: Parser (Int, String) | ||
37 | parseHeight = do | ||
38 | v <- many1 digit | ||
39 | unit <- choice $ map string ["cm", "in"] | ||
40 | return (read v, unit) | ||
41 | hgt s = case parse parseHeight "hgt" s of | ||
42 | Right (v, "cm") -> v >= 150 && v <= 193 | ||
43 | Right (v, "in") -> v >= 59 && v <= 76 | ||
44 | _ -> False | ||
45 | |||
46 | parseColor = char '#' >> many hexDigit | ||
47 | hcl :: String -> Bool | ||
48 | hcl s = case parse parseColor "hcl" s of | ||
49 | Right c -> length c == 6 | ||
50 | Left _ -> False | ||
51 | |||
52 | |||
53 | ecl :: String -> Bool | ||
54 | ecl = flip elem ["amb", "blu", "brn", "gry", "grn", "hzl", "oth"] | ||
55 | |||
56 | parsePid = replicateM 9 digit | ||
57 | pid :: String -> Bool | ||
58 | pid s = isRight $ parse parsePid "pid" s | ||
59 | |||
60 | doValidity :: [(String, String)] -> Bool | ||
61 | doValidity ls = all ((== True) . ($ ls)) [ byr . assocGet "byr" | ||
62 | , iyr . assocGet "iyr" | ||
63 | , eyr . assocGet "eyr" | ||
64 | , hgt . assocGet "hgt" | ||
65 | , hcl . assocGet "hcl" | ||
66 | , ecl . assocGet "ecl" | ||
67 | , pid . assocGet "pid" | ||
68 | ] | ||
69 | |||
70 | parseLines :: [String] -> [String] | ||
71 | parseLines allLines = unwords first : next | ||
72 | where (first, rest) = break null allLines | ||
73 | next = if null rest then [] else parseLines (tail rest) | ||
74 | |||
75 | main :: IO () | ||
76 | main = do | ||
77 | n <- parseLines . lines <$> readFile "input/04" | ||
78 | let blocks = map (right . parseInput) n | ||
79 | print $ length $ filter (\p -> doCheck p && doValidity p) blocks | ||
80 | -- mapM_ print $ filter (\p -> doCheck p && doValidity p) $ map (sortOn fst) blocks | ||
81 | -- print $ length $ filter doCheck blocks | ||
82 | -- print $ length $ filter (\p -> doCheck p && doValidity p) $ map (sortOn fst) blocks | ||