Compare commits

...

2 commits

Author SHA1 Message Date
Xiretza 70bf616bad
day5: add haskell solution 2020-12-05 10:21:57 +01:00
Xiretza 930d0f2548
haskell: move oneCompleteResult to AoC module 2020-12-05 10:21:09 +01:00
3 changed files with 30 additions and 5 deletions

View file

@ -1,9 +1,16 @@
module AoC where
import Text.ParserCombinators.ReadP
(.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
f .: g = (f .) . g
infixl 8 .:
oneCompleteResult :: ReadP a -> String -> Maybe a
oneCompleteResult p s = case readP_to_S (p <* eof) s of
[(x, "")] -> Just x
_ -> Nothing
runAoC :: (Show r1, Show r2) => (String -> i) -> (i -> r1) -> (i -> r2) -> IO ()
runAoC inputTransform part1 part2 = do
contents <- inputTransform <$> getContents

View file

@ -89,11 +89,6 @@ parseFieldNames = spaceSeparated parseFieldName
parsePassport :: ReadP [Field]
parsePassport = spaceSeparated parseField
oneCompleteResult :: ReadP a -> String -> Maybe a
oneCompleteResult p s = case readP_to_S (p <* eof) s of
[(x, "")] -> Just x
_ -> Nothing
splitOnEmptyLines :: String -> [String]
splitOnEmptyLines = map (intercalate " ") . filter (not . any null) . groupBy ((==) `on` null) . lines

23
day5/day5.hs Normal file
View file

@ -0,0 +1,23 @@
import AoC
import Data.List (sort)
import Data.Maybe (fromJust)
import Numeric (readInt)
import Text.ParserCombinators.ReadP
binarify :: String -> Maybe Int
binarify = oneCompleteResult . readS_to_P $ readInt 2 (`elem` "BFLR") digitValue
where digitValue 'F' = 0
digitValue 'B' = 1
digitValue 'L' = 0
digitValue 'R' = 1
findHole :: (Enum a, Eq a) => [a] -> Maybe a
findHole (x:y:ys) | y == next = findHole $ y:ys
| otherwise = Just next
where next = succ x
findHole _ = Nothing
main = runAoC (fmap (fromJust . binarify) <$> lines) part1 part2
where part1 = foldr1 max
part2 = fromJust . findHole . sort