aboutsummaryrefslogtreecommitdiff
path: root/execs
diff options
context:
space:
mode:
authorAkshay <[email protected]>2020-12-04 08:51:24 +0000
committerAkshay <[email protected]>2020-12-04 08:51:24 +0000
commit031746bd8c349b485b4914d1788ec944b1e534a2 (patch)
tree187573bc58c1318d7292fac771cf5b28b98eea62 /execs
parent24dade573ba48d83265f88e3850958ff7e3d61bd (diff)
add initial solution to day 4
Diffstat (limited to 'execs')
-rw-r--r--execs/Day02.hs4
-rw-r--r--execs/Day04.hs82
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
38main :: IO () 38main :: IO ()
39main = do 39main = 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 @@
1module Main where
2
3import Text.ParserCombinators.Parsec
4import Text.Parsec.Char
5import Data.Either
6import Data.Maybe
7import Control.Monad
8import Data.List (sortOn)
9
10right (Right a) = a
11fields = [ "byr" , "iyr" , "eyr" , "hgt" , "hcl" , "ecl" , "pid" ]
12
13block = cell `sepBy` oneOf " \n"
14cell = do
15 tag <- many lower
16 char ':'
17 rest <- many (alphaNum <|> char '#')
18 return (tag, rest)
19
20parseInput :: String -> Either ParseError [(String, String)]
21parseInput = parse block "input"
22
23assocGet s (l:ls) = if fst l == s
24 then snd l
25 else assocGet s ls
26
27doCheck :: [(String, String)] -> Bool
28doCheck ls = all (isJust . flip lookup ls) fields
29
30checkNum lower up s = p >= lower && p <= up
31 where p = read s :: Int
32byr = checkNum 1920 2002
33iyr = checkNum 2010 2020
34eyr = checkNum 2020 2030
35
36parseHeight :: Parser (Int, String)
37parseHeight = do
38 v <- many1 digit
39 unit <- choice $ map string ["cm", "in"]
40 return (read v, unit)
41hgt 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
46parseColor = char '#' >> many hexDigit
47hcl :: String -> Bool
48hcl s = case parse parseColor "hcl" s of
49 Right c -> length c == 6
50 Left _ -> False
51
52
53ecl :: String -> Bool
54ecl = flip elem ["amb", "blu", "brn", "gry", "grn", "hzl", "oth"]
55
56parsePid = replicateM 9 digit
57pid :: String -> Bool
58pid s = isRight $ parse parsePid "pid" s
59
60doValidity :: [(String, String)] -> Bool
61doValidity 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
70parseLines :: [String] -> [String]
71parseLines allLines = unwords first : next
72 where (first, rest) = break null allLines
73 next = if null rest then [] else parseLines (tail rest)
74
75main :: IO ()
76main = 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