Minor refactorings of days 3, 4, 5, 6, 7, 9, 11, and removed alternate solution (i.e. the original one) for 9.

This commit is contained in:
Jonathan Chan 2017-12-12 00:12:51 -08:00
parent 46ca9a3347
commit ad9d3674f3
8 changed files with 49 additions and 114 deletions

2
11.hs
View File

@ -24,4 +24,4 @@ main :: IO ()
main = do main = do
coordinates <- fmap (map getCoordinates . splitOn ",") $ readFile "11.txt" coordinates <- fmap (map getCoordinates . splitOn ",") $ readFile "11.txt"
print $ getDistance $ fold coordinates print $ getDistance $ fold coordinates
print $ maximum . map getDistance $ scanl mappend mempty coordinates print $ maximum . map getDistance . scanl mappend mempty $ coordinates

13
3.hs
View File

@ -1,4 +1,6 @@
import qualified Data.Map as Map import Data.IntMap (IntMap, findWithDefault, insert, fromList)
type Store = IntMap Int
squareRoot :: Floating a => Int -> a squareRoot :: Floating a => Int -> a
squareRoot = sqrt . fromIntegral squareRoot = sqrt . fromIntegral
@ -11,13 +13,11 @@ getDownstairs n =
let level = getLevel n let level = getLevel n
in n - (8 * level - 7 + 2 * ((n - (2 * level - 1) ^ 2) `div` (2 * level))) in n - (8 * level - 7 + 2 * ((n - (2 * level - 1) ^ 2) `div` (2 * level)))
type Store = Map.Map Int Int
getValue :: Int -> Store -> Int getValue :: Int -> Store -> Int
getValue k m = Map.findWithDefault undefined k m getValue k m = findWithDefault undefined k m
computeValue :: Int -> Store -> Store computeValue :: Int -> Store -> Store
computeValue n m = Map.insert n value m computeValue n m = insert n value m
where where
level = getLevel n level = getLevel n
downstairs = getDownstairs n downstairs = getDownstairs n
@ -48,6 +48,5 @@ computeUntil max n m =
main :: IO () main :: IO ()
main = do main = do
let initialStore = Map.fromList $ zip [1..9] [1, 1, 2, 4, 5, 10, 11, 23, 25] let initialStore = fromList $ zip [1..9] [1, 1, 2, 4, 5, 10, 11, 23, 25]
print $ computeUntil 368078 10 initialStore print $ computeUntil 368078 10 initialStore

11
4.hs
View File

@ -1,14 +1,13 @@
import Data.List import Data.List (sort)
import Data.Set import Data.Set (toAscList, fromList)
isPassphraseValid :: [String] -> Bool isPassphraseValid :: [String] -> Bool
isPassphraseValid ws = sort ws == (toAscList . fromList) ws isPassphraseValid ws = sort ws == (toAscList . fromList) ws
main :: IO () main :: IO ()
main = do main = do
input <- readFile "4.txt" passphrases <- fmap (map words . lines) $ readFile "4.txt"
let passphrases = fmap words $ lines input let valids = sum $ map (fromEnum . isPassphraseValid) passphrases
let valids = sum $ fmap (fromEnum . isPassphraseValid) passphrases let stillValids = sum $ map (fromEnum . isPassphraseValid . (map sort)) passphrases
print $ valids print $ valids
let stillValids = sum $ fmap (fromEnum . isPassphraseValid . (fmap sort)) passphrases
print $ stillValids print $ stillValids

21
5.hs
View File

@ -1,27 +1,20 @@
import Data.IntMap (IntMap, insert, fromList, findWithDefault) import Data.IntMap (IntMap, insert, fromList, findWithDefault)
type Length = Int type State = (Int, Int, IntMap Int)
type Index = Int
type Steps = Int
type State = (Steps, Index, IntMap Int)
type Update = Int -> Int type Update = Int -> Int
next :: Update -> State -> State next :: Update -> State -> State
next f (steps, i, jumps) = next f (steps, i, jumps) =
let value = findWithDefault undefined i jumps let value = findWithDefault undefined i jumps
nextI = i + value in (steps + 1, i + value, insert i (f value) jumps)
nextJumps = insert i (f value) jumps
in (steps + 1, nextI, nextJumps)
getExitSteps :: Length -> Update -> State -> Int getExitSteps :: Int -> Update -> State -> Int
getExitSteps len f (steps, i, jumps) = getExitSteps len f (steps, i, jumps) =
if i >= len then steps else getExitSteps len f $! next f (steps, i, jumps) if i >= len then steps else getExitSteps len f $! next f (steps, i, jumps)
main :: IO () main :: IO ()
main = do main = do
input <- readFile "5.txt" jumpsList <- fmap (map read . lines) $ readFile "5.txt"
let jumpsList = map read $ lines input let jumpsMap = fromList $ zip [0..] jumpsList
jumpsMap = fromList $ zip [0..] jumpsList print $ getExitSteps (length jumpsList) (+1) (0, 0, jumpsMap)
len = length jumpsList print $ getExitSteps (length jumpsList) (\v -> if v >= 3 then v - 1 else v + 1) (0, 0, jumpsMap)
print $ getExitSteps len (+1) (0, 0, jumpsMap)
print $ getExitSteps len (\v -> if v >= 3 then v - 1 else v + 1) (0, 0, jumpsMap)

27
6.hs
View File

@ -1,29 +1,25 @@
import Data.Foldable (toList) import Data.Foldable (toList)
import Data.Maybe
import Data.HashMap (Map, member, insert, findWithDefault, empty) import Data.HashMap (Map, member, insert, findWithDefault, empty)
import Data.Sequence (Seq, length, update, fromList, foldlWithIndex, mapWithIndex) import Data.Sequence (Seq, update, fromList, elemIndexL, mapWithIndex)
import qualified Data.Sequence as S (length)
type Bank = Seq Int type Bank = Seq Int
type HashableBank = [Int] type Config = (Bank, Map [Int] Int)
type Config = (Bank, Map HashableBank Int)
(%) :: Int -> Int -> Int
(%) = mod (%) = mod
(//) :: Int -> Int -> Int
(//) = div (//) = div
getMaxMem :: Bank -> (Int, Int) getMaxMem :: Bank -> (Int, Int)
getMaxMem bank = getMaxMem bank =
foldlWithIndex (\(currIndex, currMax) index value -> if value > currMax then (index, value) else (currIndex, currMax)) (0, 0) bank (fromJust $ elemIndexL (maximum bank) bank, maximum bank)
nextBank :: Bank -> Bank nextBank :: Bank -> Bank
nextBank bank = nextBank bank =
let len = Data.Sequence.length bank let len = S.length bank
(index, value) = getMaxMem bank (index, value) = getMaxMem bank
zeroedBank = update index 0 bank newBank = fmap (+ value // len) $ update index 0 bank
mappedBank = fmap (+ value // len) zeroedBank indices = fmap (% len) [index + 1..index + value % len]
indicesToUpdate = fmap ((% len) . (+ index)) [1..value % len] in mapWithIndex (\i v -> v + fromEnum (i `elem` indices)) newBank
in mapWithIndex (\i v -> if i `elem` indicesToUpdate then v + 1 else v) mappedBank
cycles :: Int -> Config -> (Int, Int) cycles :: Int -> Config -> (Int, Int)
@ -37,6 +33,5 @@ cycles prevCount (prevBank, banks) =
main :: IO () main :: IO ()
main = do main = do
input <- readFile "6.txt" bank <- fmap (fromList . map read . words) $ readFile "6.txt"
let bank = fromList $ fmap read $ words input :: Bank
print $ cycles 0 (bank, empty) print $ cycles 0 (bank, empty)

13
7.hs
View File

@ -16,10 +16,10 @@ minOrZero 0 y = y
minOrZero x y = min x y minOrZero x y = min x y
getWeights :: Forest (Weight, Int) -> [Weight] getWeights :: Forest (Weight, Int) -> [Weight]
getWeights ts = fmap (\(Node (_, weight) _) -> weight) ts getWeights = fmap (\(Node (_, weight) _) -> weight)
findRootWithWeight :: Int -> Forest (Weight, Int) -> Weight findRootWithWeight :: Int -> Forest (Weight, Int) -> Weight
findRootWithWeight w ts = foldr (\(Node (root, weight) _) acc -> if weight == w then root else acc) 0 ts findRootWithWeight w = foldr (\(Node (root, weight) _) acc -> if weight == w then root else acc) 0
-- input: [Weight > 0] where all weights are the same except one -- input: [Weight > 0] where all weights are the same except one
-- output: (difference between the median weight and the minority weight, the minority weight) -- output: (difference between the median weight and the minority weight, the minority weight)
@ -35,7 +35,7 @@ parseLine :: String -> (Program, (Weight, Programs))
parseLine line = parseLine line =
let nameAndWeight : programsString : _ = splitOn ")" line let nameAndWeight : programsString : _ = splitOn ")" line
name : weight : _ = splitOn " (" nameAndWeight name : weight : _ = splitOn " (" nameAndWeight
programs = discardEmpty $ splitOn ", " $ last $ splitOn " -> " programsString programs = discardEmpty . splitOn ", " . last . splitOn " -> " $ programsString
in (name, (read weight, programs)) in (name, (read weight, programs))
getBottom :: Map Program (Weight, Programs) -> [(Program, (Weight, Programs))] -> Program getBottom :: Map Program (Weight, Programs) -> [(Program, (Weight, Programs))] -> Program
@ -54,7 +54,7 @@ mapToTree m = unfoldTree (\s -> findWithDefault undefined s m)
cumulate :: Tree Weight -> Tree (Weight, Int) cumulate :: Tree Weight -> Tree (Weight, Int)
cumulate (Node root forest) = cumulate (Node root forest) =
let newForest = map cumulate forest let newForest = map cumulate forest
cumulativeWeight = (+ root) . sum $ getWeights newForest cumulativeWeight = (+ root) . sum . getWeights $ newForest
in Node { rootLabel = (root, cumulativeWeight), subForest = newForest } in Node { rootLabel = (root, cumulativeWeight), subForest = newForest }
findBalanced :: Tree (Weight, Int) -> Int findBalanced :: Tree (Weight, Int) -> Int
@ -66,9 +66,8 @@ findBalanced (Node _ forest) =
main :: IO () main :: IO ()
main = do main = do
input <- readFile "7.txt" programsList <- fmap (map parseLine . lines) $ readFile "7.txt"
let programsList = map parseLine $ lines input let programsMap = fromList programsList
programsMap = fromList programsList
bottomName = getBottom programsMap programsList bottomName = getBottom programsMap programsList
balanced = findBalanced . cumulate $ mapToTree programsMap bottomName balanced = findBalanced . cumulate $ mapToTree programsMap bottomName
-- programsTree = mapToTree programsMap bottomName -- programsTree = mapToTree programsMap bottomName

58
9.hs
View File

@ -1,49 +1,15 @@
scoreAndCount :: String -> (Int, Int)
removeCancelled :: String -> String scoreAndCount str =
removeCancelled str = let (_, _, _, score, count) = foldl f (False, False, 1, 0, 0) str
let (_, removed) = foldl (\(prev, rs) curr -> in (score, count)
case prev of where f (isCancel, isGarbage, level, score, count) curr
'!' -> ('\0', rs) | isCancel = (False, isGarbage, level, score, count)
'\0' -> (curr, rs) | isGarbage = (curr == '!', curr /= '>', level, score, count + (fromEnum $ curr /= '>' && curr /= '!'))
_ -> (curr, prev : rs)) | curr == '{' = (False, False, level + 1, score + level, count)
(head str, "") (tail str) | curr == '}' = (False, False, level - 1, score, count)
in reverse $ filter (/= '\0') removed | curr == ',' = (False, False, level, score, count)
| curr == '<' = (False, True, level, score, count)
removeGarbage :: String -> String
removeGarbage str =
let (_, removed) = foldl (\(isGarbage, rs) curr ->
if isGarbage
then (curr /= '>', rs)
else (curr == '<',
if curr == '<'
then rs
else curr : rs))
(False, "") str
in reverse $ filter (/= ',') removed
countNonGarbage :: String -> Int
countNonGarbage str =
let (_, removed) = foldl (\(isGarbage, rs) curr ->
if isGarbage
then (curr /= '>',
if curr == '>'
then rs
else curr : rs)
else (curr == '<', rs))
(False, "") str
in length removed
countGroups :: String -> Int
countGroups str =
let (_, total) = foldl (\(score, acc) curr ->
case curr of
'{' -> (score + 1, acc + score)
'}' -> (score - 1, acc))
(1, 0) str
in total
main :: IO () main :: IO ()
main = do main = do
input <- readFile "9.txt" readFile "9.txt" >>= print . scoreAndCount
print $ countGroups . removeGarbage . removeCancelled $ input
print $ countNonGarbage . removeCancelled $ input

View File

@ -1,16 +0,0 @@
scoreAndCount :: String -> (Int, Int)
scoreAndCount str =
let (_, _, _, score, count) = foldl f (False, False, 1, 0, 0) str
in (score, count)
where f (isCancel, isGarbage, level, score, count) curr
| isCancel = (False, isGarbage, level, score, count)
| isGarbage = (curr == '!', curr /= '>', level, score, count + (fromEnum $ curr /= '>' && curr /= '!'))
| curr == '{' = (False, False, level + 1, score + level, count)
| curr == '}' = (False, False, level - 1, score, count)
| curr == ',' = (False, False, level, score, count)
| curr == '<' = (False, True, level, score, count)
main :: IO ()
main = do
input <- readFile "9.txt"
print $ scoreAndCount input