haskell: add simple run harness

This commit is contained in:
Xiretza 2020-12-05 09:53:27 +01:00
parent 771072c130
commit 3b0fde248f
Signed by: xiretza
GPG Key ID: 17B78226F7139993
4 changed files with 26 additions and 26 deletions

11
common/AoC.hs Normal file
View File

@ -0,0 +1,11 @@
module AoC where
(.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
f .: g = (f .) . g
infixl 8 .:
runAoC :: (Show r1, Show r2) => (String -> i) -> (i -> r1) -> (i -> r2) -> IO ()
runAoC inputTransform part1 part2 = do
contents <- inputTransform <$> getContents
print $ part1 contents
print $ part2 contents

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TypeApplications #-}
import AoC
import Data.List
import Data.Maybe
@ -7,6 +7,5 @@ import Control.Monad
find_n_summing :: (Num a, Eq a) => a -> Int -> [a] -> Maybe [a]
find_n_summing to = (find ((to ==) . sum) .) . replicateM
main = do
nums <- fmap read <$> lines <$> readFile "input.txt"
mapM_ print $ product <$> fromJust <$> flip (find_n_summing 2020) nums <$> [2, 3]
main = runAoC (fmap read <$> lines) (solution 2) (solution 3)
where solution = product . fromJust .: find_n_summing 2020

View File

@ -1,3 +1,5 @@
import AoC
import Control.Applicative (empty)
import Control.Monad.Zip (mzip)
import Data.List (intercalate)
@ -6,9 +8,8 @@ import Data.Maybe (catMaybes)
compose2 :: (a' -> b' -> c) -> (a -> a') -> (b -> b') -> a -> b -> c
compose2 f g h x y = f (g x) (h y)
(.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
f .: g = (f .) . g
infixl 8 .:
(??) :: Functor f => f (a -> b) -> a -> f b
f ?? x = fmap ($ x) f
countHits :: (Int, Int) -> [[Bool]] -> Int
countHits = length . filterMap lookup . catMaybes .: compose2 (zipWith mzip) maybeIndices justLines
@ -22,8 +23,6 @@ countHits = length . filterMap lookup . catMaybes .: compose2 (zipWith mzip) may
treeCharToBool :: Char -> Bool
treeCharToBool = (== '#')
main = do
charLines <- lines <$> readFile "input.txt"
let boolLines = cycle <$> map treeCharToBool <$> charLines
print $ countHits (3, 1) boolLines
print $ product $ flip countHits boolLines <$> [(1,1), (3,1), (5,1), (7,1), (1,2)]
main = runAoC (fmap (cycle . map treeCharToBool) <$> lines) part1 part2
where part1 = countHits (3, 1)
part2 = product . (fmap countHits [(1,1), (3,1), (5,1), (7,1), (1,2)] ??)

View File

@ -1,3 +1,5 @@
import AoC
import Control.Applicative ((<|>))
import Control.Monad (guard, mfilter)
import Data.Char (isDigit)
@ -39,10 +41,6 @@ fieldSpecs = [ ("byr", BirthYear <$> parseYearIn 1920 2002)
where parseYearIn = flip mfilter (parseNumber 4) .: within
parseHexDigit = choice . map char $ ['0'..'9']++['a'..'f']
(.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
f .: g = (f .) . g
infixl 8 .:
within :: Ord a => a -> a -> a -> Bool
within a b x = a <= x && x <= b
@ -92,7 +90,7 @@ parsePassport :: ReadP [Field]
parsePassport = spaceSeparated parseField
oneCompleteResult :: ReadP a -> String -> Maybe a
oneCompleteResult p s = case readP_to_S p s of
oneCompleteResult p s = case readP_to_S (p <* eof) s of
[(x, "")] -> Just x
_ -> Nothing
@ -103,13 +101,6 @@ hasAllRequiredFields :: String -> Bool
hasAllRequiredFields = maybe False containsAllFields . fieldNames
where requiredFieldNames = ["byr", "iyr", "eyr", "hgt", "hcl", "ecl", "pid"]
containsAllFields fields = all (`elem` fields) requiredFieldNames
fieldNames = oneCompleteResult (parseFieldNames <* eof)
fieldNames = oneCompleteResult parseFieldNames
main = do
batches <- splitOnEmptyLines <$> readFile "input.txt"
let withRequiredFields = filter hasAllRequiredFields batches
print $ length withRequiredFields
let passports = mapMaybe (oneCompleteResult (parsePassport <* eof)) withRequiredFields
print $ length passports
main = runAoC (filter hasAllRequiredFields . splitOnEmptyLines) (length) (length . mapMaybe (oneCompleteResult parsePassport))