haskell: 2015 05a

This commit is contained in:
Maciej Jur 2024-08-06 22:29:35 +02:00
parent 637232a196
commit e2176c7893
Signed by: kamov
GPG key ID: 191CBFF5F72ECAFD
4 changed files with 71 additions and 21 deletions

View file

@ -1,19 +1,24 @@
{-# LANGUAGE TypeApplications #-} {-# LANGUAGE ImportQualifiedPost #-}
module Main where module Main where
import qualified Day01 import Data.Text (Text)
import qualified Day02 import Data.Text.IO qualified as TIO
import qualified Day03 import Day01 qualified
import Day02 qualified
import Day03 qualified
import Day04 qualified
import Day05 qualified
import Text.Printf (printf) import Text.Printf (printf)
readDay :: Int -> IO String readDay :: Int -> IO Text
readDay n = readFile $ getPath n readDay n = TIO.readFile $ getPath n
where where
getPath n = "../.inputs/" <> printf "%02d" n getPath n = "../.inputs/" <> printf "%02d" n
main :: IO () main :: IO ()
main = do main = do
content <- readDay 2 content <- Day05.parse <$> readDay 5
let parsed = Day02.parse content print $ Day05.solveA content
print $ Day02.solveA parsed
print @Int $ Day02.solveB parsed -- print @Int $ Day05.solveB parsed

View file

@ -21,10 +21,7 @@ library
Day02 Day02
Day03 Day03
Day04 Day04
Day05
default-extensions:
ImportQualifiedPost
OverloadedStrings
-- Modules included in this library but not exported. -- Modules included in this library but not exported.
-- other-modules: -- other-modules:
@ -48,6 +45,7 @@ executable haskell
build-depends: build-depends:
aoc2015, aoc2015,
base >=4.16.4.0, base >=4.16.4.0,
text >=2.1.1,
hs-source-dirs: app hs-source-dirs: app
default-language: Haskell2010 default-language: Haskell2010

View file

@ -1,3 +1,6 @@
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE OverloadedStrings #-}
module Day04 (solveA, solveB) where module Day04 (solveA, solveB) where
import Crypto.Hash.MD5 (hash) import Crypto.Hash.MD5 (hash)
@ -7,20 +10,20 @@ import Data.ByteString qualified as BS
import Data.ByteString.Char8 qualified as Char8 import Data.ByteString.Char8 qualified as Char8
import Text.Printf (printf) import Text.Printf (printf)
hashHex :: String -> String hashHex :: ByteString -> String
hashHex = concatMap (printf "%02x") . BS.unpack . hash . Char8.pack hashHex = concatMap (printf "%02x") . BS.unpack . hash
test :: String test :: ByteString
test = "ckczppom" test = "ckczppom"
solve :: Int -> String -> Integer solve :: Int -> ByteString -> Integer
solve zeros key = fst . head . filter (isMatch . snd) . map toHash $ [1 ..] solve zeros key = fst . head . filter (isMatch . snd) . map toHash $ [1 ..]
where where
toHash n = (n, hashHex $ key <> show n) toHash n = (n, hashHex $ key <> Char8.pack (show n))
isMatch = all (== '0') . take zeros isMatch = all (== '0') . take zeros
solveA :: String -> Integer solveA :: ByteString -> Integer
solveA = solve 5 solveA = solve 5
solveB :: String -> Integer solveB :: ByteString -> Integer
solveB = solve 6 solveB = solve 6

View file

@ -0,0 +1,44 @@
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
module Day05 (parse, solveA) where
import Control.Monad (foldM)
import Control.Monad qualified as T
import Data.Either (fromLeft)
import Data.Maybe (fromMaybe, isNothing)
import Data.Text (Text)
import Data.Text qualified as T
parse :: Text -> [Text]
parse = T.lines
isVovel :: Char -> Bool
isVovel c = elem @[] c "aeiou"
isWrong :: String -> Bool
isWrong cs = cs `elem` ["ab", "cd", "pq", "xy"]
isNice :: Text -> Bool
isNice = maybe False (check . snd) . foldM next ('_', (False, 0)) . T.unpack
where
check :: (Bool, Int) -> Bool
check (double, vowels) = double && vowels >= 3
next :: ((Char, (Bool, Int)) -> Char -> Maybe (Char, (Bool, Int)))
next (prev, (double, vowels)) char =
let double' = double || prev == char
vowels' = if isVovel char then vowels + 1 else vowels
in if isWrong [prev, char]
then Nothing
else Just (char, (double', vowels'))
solveA :: [Text] -> Int
solveA = length . filter isNice
test :: Text
test = "dvszwmarrgswjxmbau"
-- $> isNice test
solveB = undefined