Add day2 and readd day1

This commit is contained in:
Sijmen 2018-12-02 16:52:36 +01:00
parent 68b10c50b1
commit 8f030af74c
5 changed files with 67 additions and 0 deletions

2
.gitignore vendored
View file

@ -1,7 +1,9 @@
# Ignore everything without extension
*
!*.*
!*/
*.in
*.hi
*.o
*.prof

8
Day1/Day1A.hs Normal file
View file

@ -0,0 +1,8 @@
module Day1A where
read' :: String -> Int
read' ('+':str) = read str
read' str = read str
main :: IO ()
main = interact $ show . sum . map read' . lines

14
Day1/Day1B.hs Normal file
View file

@ -0,0 +1,14 @@
module Day1B where
import Day1A (read')
import qualified Data.IntSet as S
handle :: Int -> S.IntSet -> [Int] -> Int
handle freq history (nextDelta:xs)
| S.member freq history = freq -- When the frequency is in the history set, return it
| otherwise = handle (freq + nextDelta) (S.insert freq history) xs -- Recurse otherwise
handle _ _ _ = error "xs should not be empty :("
main :: IO ()
main = interact $ show . handle 0 S.empty . deltaFreqs
where deltaFreqs = cycle . map read' . lines -- Convert input to Ints and repeat infinitely

18
Day2/Day2A.hs Normal file
View file

@ -0,0 +1,18 @@
module Day2A where
import qualified Data.IntMap as IM
import Data.Char (ord)
out :: String -> Int -> Int
out id' n = min (length $ IM.filter (==n) counts) 1
where counts = foldr (\c -> IM.insertWith (+) (ord c) 1) IM.empty id'
handleId :: String -> (Int, Int)
handleId id' = (out id' 2, out id' 3)
add2 :: Num a => (a, a) -> (a, a) -> (a, a)
add2 (a, b) (x, y) = (a + x, b + y)
main :: IO ()
main = interact $ show . uncurry (*) . counts . lines
where counts = foldr (add2 . handleId) (0, 0)

25
Day2/Day2B.hs Normal file
View file

@ -0,0 +1,25 @@
{-# LANGUAGE TupleSections #-}
module Day2B where
import Data.List (find)
import qualified Data.Sequence as S
import qualified Data.Foldable as F
dist' :: Int -> (S.Seq Char) -> String -> String -> (Int, String)
dist' n common (a:x) (b:y)
| a == b = dist' n (common S.|> a) x y
| otherwise = dist' (n + 1) common x y
dist' n common _ _ = (n, F.toList common)
dist :: String -> String -> (Int, String)
dist = dist' 0 S.empty
combinations :: [String] -> [(String, String)]
combinations (x:y:xs) = (x, y):(combinations (y:xs))
combinations [] = []
distances :: [(String, String)] -> String
distances xs = result
where Just(_, result) = find (\(x, _) -> x == 1) $ map (uncurry dist) xs
main :: IO ()
main = interact $ distances . combinations . lines