Day 2 parts 1 and 2
This commit is contained in:
parent
6674ab9ed0
commit
f577913aa1
1 changed files with 76 additions and 1 deletions
77
day2/main.hs
77
day2/main.hs
|
@ -1,10 +1,85 @@
|
||||||
#! /usr/bin/env -S"ANSWER=42" nix-shell
|
#! /usr/bin/env -S"ANSWER=42" nix-shell
|
||||||
#! nix-shell -p ghcid
|
#! nix-shell -p ghcid
|
||||||
#! nix-shell -p "haskellPackages.ghcWithPackages (p: with p; [shower])"
|
#! nix-shell -p "haskellPackages.ghcWithPackages (p: with p; [attoparsec])"
|
||||||
#! nix-shell -i "ghcid -c 'ghci -Wall' -T main"
|
#! nix-shell -i "ghcid -c 'ghci -Wall' -T main"
|
||||||
|
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
|
||||||
|
import Data.Attoparsec.Text
|
||||||
|
import Data.Text (pack)
|
||||||
|
import Data.Maybe (catMaybes)
|
||||||
|
import Data.Bits (xor)
|
||||||
|
|
||||||
|
testData :: [String]
|
||||||
|
testData = [ "1-3 a: abcde"
|
||||||
|
, "1-3 b: cdefg"
|
||||||
|
, "2-9 c: ccccccccc"
|
||||||
|
]
|
||||||
|
|
||||||
|
data Input = Input {
|
||||||
|
atLeast :: Int
|
||||||
|
, notMore :: Int
|
||||||
|
, character :: Char
|
||||||
|
, password :: String
|
||||||
|
} deriving Show
|
||||||
|
|
||||||
|
inputParser :: Parser Input
|
||||||
|
inputParser = do
|
||||||
|
atLeast' <- decimal
|
||||||
|
_ <- char '-'
|
||||||
|
notMore' <- decimal
|
||||||
|
_ <- space
|
||||||
|
character' <- letter
|
||||||
|
_ <- char ':'
|
||||||
|
_ <- space
|
||||||
|
password' <- many1 letter
|
||||||
|
return $ Input atLeast' notMore' character' password'
|
||||||
|
|
||||||
|
parseInputLine :: String -> Maybe Input
|
||||||
|
parseInputLine s = eitherToMaybe $ parseOnly inputParser (pack s)
|
||||||
|
|
||||||
|
eitherToMaybe :: Either a b -> Maybe b
|
||||||
|
eitherToMaybe (Right e) = Just e
|
||||||
|
eitherToMaybe (Left _) = Nothing
|
||||||
|
|
||||||
|
match' :: Char -> Char -> Int
|
||||||
|
match' c1 c2 | c1 == c2 = 1
|
||||||
|
match' _ _ = 0
|
||||||
|
|
||||||
|
-- How many passwords are valid according to their policies?
|
||||||
|
|
||||||
|
validatePassword1 :: Input -> Bool
|
||||||
|
validatePassword1 (Input min' max' char' pass) =
|
||||||
|
c >= min' && c <= max'
|
||||||
|
where
|
||||||
|
c = foldl (\acc c' -> acc + match' char' c') 0 pass
|
||||||
|
|
||||||
|
-- How many passwords are valid according to the new interpretation of the
|
||||||
|
-- policies?
|
||||||
|
|
||||||
|
validatePassword2 :: Input -> Bool
|
||||||
|
validatePassword2 (Input pos1 pos2 char' pass) =
|
||||||
|
(pass !! (pos1-1) == char') `xor` (pass !! (pos2-1) == char')
|
||||||
|
|
||||||
|
validateLine :: (Input -> Bool) -> String -> Maybe Bool
|
||||||
|
validateLine f s = do
|
||||||
|
i <- parseInputLine s
|
||||||
|
pure $ f i
|
||||||
|
|
||||||
|
countTrue :: [Bool] -> Int
|
||||||
|
countTrue = length . filter (== True)
|
||||||
|
|
||||||
|
solveDay2Part1 :: [String] -> Int
|
||||||
|
solveDay2Part1 = countTrue . catMaybes . (map (validateLine validatePassword1))
|
||||||
|
|
||||||
|
solveDay2Part2 :: [String] -> Int
|
||||||
|
solveDay2Part2 = countTrue . catMaybes . (map (validateLine validatePassword2))
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
putStrLn "Day 2 - Part 1"
|
putStrLn "Day 2 - Part 1"
|
||||||
|
inputData <- readFile "./day2/input"
|
||||||
|
print $ solveDay2Part1 testData
|
||||||
|
print $ solveDay2Part1 (lines inputData)
|
||||||
|
print $ solveDay2Part2 testData
|
||||||
|
print $ solveDay2Part2 (lines inputData)
|
||||||
|
|
Loading…
Reference in a new issue