Skip to content

Instantly share code, notes, and snippets.

@Arkham

Arkham/Main.hs Secret

Created January 6, 2021 11:49
Show Gist options
  • Star 4 You must be signed in to star a gist
  • Fork 1 You must be signed in to fork a gist
  • Save Arkham/f3b76516b8a9c07cf2b0038871c60657 to your computer and use it in GitHub Desktop.
Save Arkham/f3b76516b8a9c07cf2b0038871c60657 to your computer and use it in GitHub Desktop.
module Main where
import Control.Monad (guard)
import Data.Either (rights)
import qualified Data.List.Split as S
import qualified Text.Parsec as P
import Text.Parsec.Perm (permute, (<$$>), (<|?>), (<||>))
import Text.Parsec.String (Parser)
main :: IO ()
main = do
contents <- readFile "input.txt"
let passports =
rights $
map
(P.parse passportParser "")
(S.splitOn "\n\n" contents)
print $ length passports
data Passport = Passport
{ birthYear :: Int,
issueYear :: Int,
expirationYear :: Int,
height :: Height,
hairColor :: String,
eyeColor :: String,
passportId :: String,
countryId :: Maybe Int
}
yearParser :: String -> (Int, Int) -> Parser Int
yearParser value (rangeStart, rangeEnd) = do
P.string value
P.char ':'
value <- P.count 4 P.digit
P.spaces
let int = read value
guard (int >= rangeStart && int <= rangeEnd)
return int
byrParser :: Parser Int
byrParser = do
yearParser "byr" (1920, 2002)
iyrParser :: Parser Int
iyrParser = do
yearParser "iyr" (2010, 2020)
eyrParser :: Parser Int
eyrParser = do
yearParser "eyr" (2020, 2030)
data Height
= InCms Int
| InInches Int
deriving (Eq, Show)
-- hgt (Height) - a number followed by either cm or in:
-- If cm, the number must be between 150 and 193.
-- If in, the number must be between 59 and 76.
heightParser :: Parser Height
heightParser = do
P.string "hgt"
P.char ':'
digits <- P.many1 P.digit
let value = read digits
result <- unitParser value
case result of
InCms _ ->
guard (value >= 150 && value <= 193)
InInches _ ->
guard (value >= 59 && value <= 76)
P.spaces
return result
unitParser :: Int -> Parser Height
unitParser value =
let cmParser = do
P.string "cm"
return (InCms value)
inParser = do
P.string "in"
return (InInches value)
in P.choice [cmParser, inParser]
-- hcl (Hair Color) - a '#' followed by six chars 0-9 or a-f.
hairColorParser :: Parser String
hairColorParser = do
P.string "hcl"
P.char ':'
P.char '#'
v <- P.count 6 (P.oneOf "0123456789abcdef")
P.spaces
return v
-- ecl (Eye Color) - one of: amb blu brn gry grn hzl oth.
eyeColorParser :: Parser String
eyeColorParser = do
P.string "ecl"
P.char ':'
v <-
P.choice $
map
(P.try . P.string)
[ "amb",
"blu",
"brn",
"gry",
"grn",
"hzl",
"oth"
]
P.spaces
return v
-- pid (Passport ID) - a nine-digit number.
passportIdParser :: Parser String
passportIdParser = do
P.string "pid"
P.char ':'
v <- P.count 9 P.digit
P.spaces
return v
-- cid (Country ID) - ignored, missing or not.
countryIdParser :: Parser Int
countryIdParser = do
P.string "cid"
P.char ':'
value <- P.many1 P.digit
P.spaces
return $ read value
passportParser :: Parser Passport
passportParser =
permute $
Passport <$$> byrParser
<||> iyrParser
<||> P.try eyrParser
<||> P.try heightParser
<||> P.try hairColorParser
<||> P.try eyeColorParser
<||> passportIdParser
<|?> (Nothing, Just <$> countryIdParser)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment