Day 14, parts 1 & 2: Initial solution.

This commit is contained in:
Jesse D. McDonald 2018-12-16 21:49:30 -06:00
parent efd27c2103
commit adadcb88fc
3 changed files with 49 additions and 0 deletions

33
Day14/Common.hs Executable file
View File

@ -0,0 +1,33 @@
module Common where
import Data.Function (fix)
import Data.Word
import qualified Data.List as L
input :: Num a => a
input = 170641
scores :: () -> [Word8]
scores () = fix $ \ss ->
3 : 7 : concat (L.unfoldr (Just . step (quickLookup ss)) (0, 1, 2))
digits :: Num a => Int -> [a]
digits = map (\c -> fromIntegral (fromEnum c - fromEnum '0')) . show
step :: (Int -> Word8) -> (Int, Int, Int) -> ([Word8], (Int, Int, Int))
step ss (a, b, n) = (rs, (a', b', n'))
where
sa = fromIntegral (ss a)
sb = fromIntegral (ss b)
rs = digits (sa + sb)
n' = n + length rs
a' = (a + 1 + sa) `mod` n'
b' = (b + 1 + sb) `mod` n'
quickLookup :: [a] -> Int -> a
quickLookup xs = \n -> if n < 10 then xs !! n
else (nextLevel (n `div` 10)) !! (n `mod` 10)
where
nextLevel = quickLookup $ decimate $ L.tails xs
decimate [] = []
decimate xs = let (as, bs) = splitAt 10 xs in head as : decimate bs

5
Day14/Part1.hs Executable file
View File

@ -0,0 +1,5 @@
#! /usr/bin/env stack
-- stack --resolver lts-12.20 --install-ghc script
module Main where
import Common
main = print $ take 10 $ drop input $ scores ()

11
Day14/Part2.hs Executable file
View File

@ -0,0 +1,11 @@
#! /usr/bin/env stack
-- stack --resolver lts-12.20 --install-ghc script
module Main where
import Common
import Data.List (tails)
main = print $ fst $ head
$ dropWhile ((/= inputDigits) . take (length inputDigits) . snd)
$ zip [0..] $ tails $ scores ()
where inputDigits = digits input