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:
parent
46ca9a3347
commit
ad9d3674f3
2
11.hs
2
11.hs
|
@ -24,4 +24,4 @@ main :: IO ()
|
|||
main = do
|
||||
coordinates <- fmap (map getCoordinates . splitOn ",") $ readFile "11.txt"
|
||||
print $ getDistance $ fold coordinates
|
||||
print $ maximum . map getDistance $ scanl mappend mempty coordinates
|
||||
print $ maximum . map getDistance . scanl mappend mempty $ coordinates
|
13
3.hs
13
3.hs
|
@ -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 = sqrt . fromIntegral
|
||||
|
@ -11,13 +13,11 @@ getDownstairs n =
|
|||
let level = getLevel n
|
||||
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 k m = Map.findWithDefault undefined k m
|
||||
getValue k m = findWithDefault undefined k m
|
||||
|
||||
computeValue :: Int -> Store -> Store
|
||||
computeValue n m = Map.insert n value m
|
||||
computeValue n m = insert n value m
|
||||
where
|
||||
level = getLevel n
|
||||
downstairs = getDownstairs n
|
||||
|
@ -48,6 +48,5 @@ computeUntil max n m =
|
|||
|
||||
main :: IO ()
|
||||
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
|
||||
|
11
4.hs
11
4.hs
|
@ -1,14 +1,13 @@
|
|||
import Data.List
|
||||
import Data.Set
|
||||
import Data.List (sort)
|
||||
import Data.Set (toAscList, fromList)
|
||||
|
||||
isPassphraseValid :: [String] -> Bool
|
||||
isPassphraseValid ws = sort ws == (toAscList . fromList) ws
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
input <- readFile "4.txt"
|
||||
let passphrases = fmap words $ lines input
|
||||
let valids = sum $ fmap (fromEnum . isPassphraseValid) passphrases
|
||||
passphrases <- fmap (map words . lines) $ readFile "4.txt"
|
||||
let valids = sum $ map (fromEnum . isPassphraseValid) passphrases
|
||||
let stillValids = sum $ map (fromEnum . isPassphraseValid . (map sort)) passphrases
|
||||
print $ valids
|
||||
let stillValids = sum $ fmap (fromEnum . isPassphraseValid . (fmap sort)) passphrases
|
||||
print $ stillValids
|
21
5.hs
21
5.hs
|
@ -1,27 +1,20 @@
|
|||
import Data.IntMap (IntMap, insert, fromList, findWithDefault)
|
||||
|
||||
type Length = Int
|
||||
type Index = Int
|
||||
type Steps = Int
|
||||
type State = (Steps, Index, IntMap Int)
|
||||
type State = (Int, Int, IntMap Int)
|
||||
type Update = Int -> Int
|
||||
|
||||
next :: Update -> State -> State
|
||||
next f (steps, i, jumps) =
|
||||
let value = findWithDefault undefined i jumps
|
||||
nextI = i + value
|
||||
nextJumps = insert i (f value) jumps
|
||||
in (steps + 1, nextI, nextJumps)
|
||||
in (steps + 1, i + value, insert i (f value) jumps)
|
||||
|
||||
getExitSteps :: Length -> Update -> State -> Int
|
||||
getExitSteps :: Int -> Update -> State -> Int
|
||||
getExitSteps len f (steps, i, jumps) =
|
||||
if i >= len then steps else getExitSteps len f $! next f (steps, i, jumps)
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
input <- readFile "5.txt"
|
||||
let jumpsList = map read $ lines input
|
||||
jumpsMap = fromList $ zip [0..] jumpsList
|
||||
len = length jumpsList
|
||||
print $ getExitSteps len (+1) (0, 0, jumpsMap)
|
||||
print $ getExitSteps len (\v -> if v >= 3 then v - 1 else v + 1) (0, 0, jumpsMap)
|
||||
jumpsList <- fmap (map read . lines) $ readFile "5.txt"
|
||||
let jumpsMap = fromList $ zip [0..] jumpsList
|
||||
print $ getExitSteps (length jumpsList) (+1) (0, 0, jumpsMap)
|
||||
print $ getExitSteps (length jumpsList) (\v -> if v >= 3 then v - 1 else v + 1) (0, 0, jumpsMap)
|
27
6.hs
27
6.hs
|
@ -1,29 +1,25 @@
|
|||
import Data.Foldable (toList)
|
||||
import Data.Maybe
|
||||
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 HashableBank = [Int]
|
||||
type Config = (Bank, Map HashableBank Int)
|
||||
|
||||
(%) :: Int -> Int -> Int
|
||||
type Bank = Seq Int
|
||||
type Config = (Bank, Map [Int] Int)
|
||||
(%) = mod
|
||||
|
||||
(//) :: Int -> Int -> Int
|
||||
(//) = div
|
||||
|
||||
getMaxMem :: Bank -> (Int, Int)
|
||||
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 =
|
||||
let len = Data.Sequence.length bank
|
||||
let len = S.length bank
|
||||
(index, value) = getMaxMem bank
|
||||
zeroedBank = update index 0 bank
|
||||
mappedBank = fmap (+ value // len) zeroedBank
|
||||
indicesToUpdate = fmap ((% len) . (+ index)) [1..value % len]
|
||||
in mapWithIndex (\i v -> if i `elem` indicesToUpdate then v + 1 else v) mappedBank
|
||||
newBank = fmap (+ value // len) $ update index 0 bank
|
||||
indices = fmap (% len) [index + 1..index + value % len]
|
||||
in mapWithIndex (\i v -> v + fromEnum (i `elem` indices)) newBank
|
||||
|
||||
|
||||
cycles :: Int -> Config -> (Int, Int)
|
||||
|
@ -37,6 +33,5 @@ cycles prevCount (prevBank, banks) =
|
|||
|
||||
main :: IO ()
|
||||
main = do
|
||||
input <- readFile "6.txt"
|
||||
let bank = fromList $ fmap read $ words input :: Bank
|
||||
bank <- fmap (fromList . map read . words) $ readFile "6.txt"
|
||||
print $ cycles 0 (bank, empty)
|
||||
|
|
13
7.hs
13
7.hs
|
@ -16,10 +16,10 @@ minOrZero 0 y = y
|
|||
minOrZero x y = min x y
|
||||
|
||||
getWeights :: Forest (Weight, Int) -> [Weight]
|
||||
getWeights ts = fmap (\(Node (_, weight) _) -> weight) ts
|
||||
getWeights = fmap (\(Node (_, weight) _) -> 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
|
||||
-- output: (difference between the median weight and the minority weight, the minority weight)
|
||||
|
@ -35,7 +35,7 @@ parseLine :: String -> (Program, (Weight, Programs))
|
|||
parseLine line =
|
||||
let nameAndWeight : programsString : _ = splitOn ")" line
|
||||
name : weight : _ = splitOn " (" nameAndWeight
|
||||
programs = discardEmpty $ splitOn ", " $ last $ splitOn " -> " programsString
|
||||
programs = discardEmpty . splitOn ", " . last . splitOn " -> " $ programsString
|
||||
in (name, (read weight, programs))
|
||||
|
||||
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 (Node root forest) =
|
||||
let newForest = map cumulate forest
|
||||
cumulativeWeight = (+ root) . sum $ getWeights newForest
|
||||
cumulativeWeight = (+ root) . sum . getWeights $ newForest
|
||||
in Node { rootLabel = (root, cumulativeWeight), subForest = newForest }
|
||||
|
||||
findBalanced :: Tree (Weight, Int) -> Int
|
||||
|
@ -66,9 +66,8 @@ findBalanced (Node _ forest) =
|
|||
|
||||
main :: IO ()
|
||||
main = do
|
||||
input <- readFile "7.txt"
|
||||
let programsList = map parseLine $ lines input
|
||||
programsMap = fromList programsList
|
||||
programsList <- fmap (map parseLine . lines) $ readFile "7.txt"
|
||||
let programsMap = fromList programsList
|
||||
bottomName = getBottom programsMap programsList
|
||||
balanced = findBalanced . cumulate $ mapToTree programsMap bottomName
|
||||
-- programsTree = mapToTree programsMap bottomName
|
||||
|
|
58
9.hs
58
9.hs
|
@ -1,49 +1,15 @@
|
|||
|
||||
removeCancelled :: String -> String
|
||||
removeCancelled str =
|
||||
let (_, removed) = foldl (\(prev, rs) curr ->
|
||||
case prev of
|
||||
'!' -> ('\0', rs)
|
||||
'\0' -> (curr, rs)
|
||||
_ -> (curr, prev : rs))
|
||||
(head str, "") (tail str)
|
||||
in reverse $ filter (/= '\0') removed
|
||||
|
||||
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
|
||||
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 $ countGroups . removeGarbage . removeCancelled $ input
|
||||
print $ countNonGarbage . removeCancelled $ input
|
||||
readFile "9.txt" >>= print . scoreAndCount
|
16
9_alt.hs
16
9_alt.hs
|
@ -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
|
Loading…
Reference in New Issue