summaryrefslogtreecommitdiff
path: root/2020/4.hs
blob: fd4d4753afa96db63c4533642e11f5fd1aa64b56 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-}
module Main (main) where

import Data.Char (isDigit, isSpace)
import Data.List (isInfixOf)
import qualified Data.Map.Strict as Map
import Data.Map.Strict (Map)
import Text.Parsec hiding (getInput, between)
import Text.Read (readMaybe)

import Input


data Pass = Pass (Map String String)
  deriving (Show)

data Field = Field { fField :: (String, String), fSep :: Bool }
  deriving (Show)

parseFields :: String -> [Field]
parseFields = either (error . show) id . parse pFields ""
  where
    pFields :: Parsec String () [Field]
    pFields =
        choice [try (spaces >> eof >> return [])
               ,(:) <$> (Field <$> pField <*> pSep) <*> pFields]

    pField :: Parsec String () (String, String)
    pField = (,) <$> sequence (replicate 3 lower) <*> (char ':' >> many1 (satisfy (not . isSpace)))

    pSep :: Parsec String () Bool
    pSep = ("\n\n" `isInfixOf`) <$> many1 space

parsePasses :: [Field] -> [Pass]
parsePasses [] = []
parsePasses fs = case break fSep fs of
                   (pre, p : post) ->
                       Pass (Map.fromList (map fField (pre ++ [p])))
                         : parsePasses post
                   (pre, []) ->
                       [Pass (Map.fromList (map fField pre))]

validate :: [(String, String -> Bool)] -> Pass -> Bool
validate vs (Pass fields) =
    all (\(key, check) -> maybe False check (Map.lookup key fields)) vs

numVor :: Int -> (Int -> Bool) -> String -> Bool
numVor len f s
  | length s == len, all isDigit s = f (read s)
  | otherwise = False

main :: IO ()
main = do
    let between l h x = l <= x && x <= h
        isHexDigit = flip elem "0123456789abcdef"
        validators =
            [("byr", numVor 4 (between 1920 2002))
            ,("iyr", numVor 4 (between 2010 2020))
            ,("eyr", numVor 4 (between 2020 2030))
            ,("hgt", \s -> case readMaybe @Int . reverse <$> splitAt 2 (reverse s) of
                             ("mc", Just n) -> between 150 193 n
                             ("ni", Just n) -> between 59 76 n
                             _ -> False)
            ,("hcl", \case '#' : c | length c == 6, all isHexDigit c -> True
                           _ -> False)
            ,("ecl", flip elem ["amb", "blu", "brn", "gry", "grn", "hzl", "oth"])
            ,("pid", numVor 9 (const True))]
        validators' = fmap (const (const True)) <$> validators
    input <- unlines <$> getInput 4
    let passes = parsePasses (parseFields input)
    print (sum [fromEnum (validate validators' p) | p <- passes])
    print (sum [fromEnum (validate validators p) | p <- passes])