├── .gitignore ├── Day1.hs ├── Day10.hs ├── Day11.hs ├── Day12.hs ├── Day13.hs ├── Day14.hs ├── Day15.hs ├── Day16.hs ├── Day17.hs ├── Day18.hs ├── Day19.hs ├── Day2.hs ├── Day20.hs ├── Day21.hs ├── Day22.hs ├── Day23.hs ├── Day23TH.hs ├── Day24.hs ├── Day25.hs ├── Day3.hs ├── Day4.hs ├── Day5.hs ├── Day6.hs ├── Day7.hs ├── Day8.hs ├── Day9.hs ├── LICENSE ├── Makefile ├── Setup.hs ├── advent.cabal ├── asm ├── Day2.asm └── input2.txt ├── input1.txt ├── input10.txt ├── input11.txt ├── input12.txt ├── input13.txt ├── input14.txt ├── input15.txt ├── input16.txt ├── input17.txt ├── input18.txt ├── input19.txt ├── input2.txt ├── input21.txt ├── input22.txt ├── input23.txt ├── input24.txt ├── input25.txt ├── input3.txt ├── input4.txt ├── input5.txt ├── input6.txt ├── input7.txt ├── input8.txt └── input9.txt /.gitignore: -------------------------------------------------------------------------------- 1 | /dist 2 | /dist-newstyle 3 | /.ghc.environment.* 4 | /stack.yaml 5 | /.stack-work 6 | .*.swp 7 | -------------------------------------------------------------------------------- /Day1.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Data.List 4 | 5 | main :: IO () 6 | main = 7 | do inp <- loadInput 8 | print (part1 inp) 9 | print (part2 inp) 10 | 11 | loadInput :: IO [Int] 12 | loadInput = map interpret <$> readFile "input1.txt" 13 | 14 | interpret :: Char -> Int 15 | interpret '(' = 1 16 | interpret ')' = -1 17 | interpret _ = 0 18 | 19 | part1 :: [Int] -> Int 20 | part1 = sum 21 | 22 | part2 :: [Int] -> Maybe Int 23 | part2 = findIndex (< 0) . partialSums 24 | 25 | partialSums :: Num a => [a] -> [a] 26 | partialSums = scanl' (+) 0 27 | -------------------------------------------------------------------------------- /Day10.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Data.List 4 | 5 | main :: IO () 6 | main = 7 | do steps <- iterate lookAndSay <$> loadInput 8 | print (length (steps !! 40)) 9 | print (length (steps !! 50)) 10 | 11 | loadInput :: IO String 12 | loadInput = head . words <$> readFile "input10.txt" 13 | 14 | lookAndSay :: String -> String 15 | lookAndSay = foldr aux [] . group 16 | where 17 | aux xs = shows (length xs) 18 | . showChar (head xs) 19 | -------------------------------------------------------------------------------- /Day11.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Data.List 4 | 5 | main :: IO () 6 | main = 7 | do key <- loadInput 8 | mapM_ putStrLn (take 2 (solutions key)) 9 | 10 | -- | Compute the list of valid passwords starting from a given one. 11 | -- Note: This process works on reversed passwords with the rules 12 | -- updated to work on reversed strings. This is to make 'nextPassword' 13 | -- easier to write. 14 | solutions :: String -> [String] 15 | solutions = map reverse . filter isGoodPassword . iterate nextPassword . reverse 16 | . startOnGood 17 | 18 | -- | Check that a string satisfies the descending and duplicate letter rules. 19 | isGoodPassword :: String -> Bool 20 | isGoodPassword p = hasPairs [] 2 p && hasDesc p 21 | 22 | -- | Test that a string has at least @count@ non-overlapping double, adjacent 23 | -- letters. 24 | hasPairs :: [Char] {- ^ pairs seen so far -} -> Int {- ^ count -} -> String -> Bool 25 | hasPairs _ 0 _ = True 26 | hasPairs seen n (x:y:z) 27 | | x == y && x `notElem` seen = hasPairs (x:seen) (n-1) z 28 | | otherwise = hasPairs seen n (y:z) 29 | hasPairs _ _ _ = False 30 | 31 | -- | Test that a string has a 3-length descending sequence. 32 | hasDesc :: String -> Bool 33 | hasDesc = any aux . tails 34 | where 35 | aux (x:y:z:_) = x == succ y && y == succ z 36 | aux _ = False 37 | 38 | -- | Load starting password from input file 39 | loadInput :: IO String 40 | loadInput = head . words <$> readFile "input11.txt" 41 | 42 | -- | Test that a character is not in the set of @"iol"@ 43 | isGoodLetter :: Char -> Bool 44 | isGoodLetter c = 'i' /= c && 'o' /= c && 'l' /= c 45 | 46 | -- | Clean out the starting prohibited letters 47 | startOnGood :: String -> String 48 | startOnGood [] = [] 49 | startOnGood (x:xs) 50 | | isGoodLetter x = x : startOnGood xs 51 | | otherwise = succ x : map (const 'a') xs 52 | 53 | -- | Increment a string from left to right while skipping 54 | -- the prohibited characters. 55 | nextPassword :: String -> String 56 | nextPassword [] = "a" 57 | nextPassword (x:xs) = 58 | case x of 59 | 'z' -> 'a' : nextPassword xs 60 | _ | isGoodLetter x' -> x' : xs 61 | | otherwise -> nextPassword (x':xs) 62 | where 63 | x' = succ x 64 | -------------------------------------------------------------------------------- /Day12.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE GeneralizedNewtypeDeriving, OverloadedStrings #-} 2 | module Main where 3 | 4 | import Data.Aeson 5 | import Data.Foldable 6 | import Data.Monoid 7 | import Data.Scientific 8 | import qualified Data.ByteString as B 9 | 10 | main :: IO () 11 | main = 12 | do input <- loadInput "input12.txt" 13 | print (sumOfNumbers input) 14 | print (sumOfNonredNumbers input) 15 | 16 | -- | Sum of all numbers in a JSON value. 17 | sumOfNumbers :: Value -> Scientific 18 | sumOfNumbers = sum . getList . numbers 19 | 20 | -- | Sum of all numbers in a JSON value after 21 | -- pruning out portions that fail the 'noRed' test. 22 | sumOfNonredNumbers :: Value -> Scientific 23 | sumOfNonredNumbers = sum . getList . nonredNumbers 24 | 25 | -- | Load the input file as a JSON value. 26 | loadInput :: FilePath -> IO Value 27 | loadInput filename = 28 | do contents <- B.readFile filename 29 | case decodeStrict' contents of 30 | Just v -> return v 31 | Nothing -> fail "Bad JSON document" 32 | 33 | -- | List of all the number values in in JSON value. 34 | numbers :: Value -> DList Scientific 35 | numbers v = 36 | case v of 37 | Number n -> singleton n 38 | Object o -> foldMap numbers o 39 | Array a -> foldMap numbers a 40 | _ -> mempty 41 | 42 | -- | List of all the number values in in JSON value 43 | -- excluding objects containing the value @"red"@. 44 | nonredNumbers :: Value -> DList Scientific 45 | nonredNumbers v = 46 | case v of 47 | Number n -> singleton n 48 | Object o | "red" `notElem` o -> foldMap nonredNumbers o 49 | Array a -> foldMap nonredNumbers a 50 | _ -> mempty 51 | 52 | ------------------------------------------------------------------------ 53 | 54 | -- | A list type that doesn't penalize left-nested appends. 55 | newtype DList a = DList (Endo [a]) deriving (Semigroup, Monoid) 56 | 57 | singleton :: a -> DList a 58 | singleton = DList . Endo . (:) 59 | 60 | getList :: DList a -> [a] 61 | getList (DList f) = appEndo f [] 62 | -------------------------------------------------------------------------------- /Day13.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Data.List 4 | import Data.Map (Map) 5 | import qualified Data.Map as Map 6 | import qualified Data.Set as Set 7 | 8 | data Edge = Edge String String 9 | deriving (Eq, Ord) 10 | 11 | edge :: String -> String -> Edge 12 | edge a b 13 | | a < b = Edge a b 14 | | otherwise = Edge b a 15 | 16 | edgeToList :: Edge -> [String] 17 | edgeToList (Edge a b) = [a,b] 18 | 19 | main :: IO () 20 | main = 21 | do input <- loadInput 22 | 23 | let people1 = uniques (concatMap edgeToList (Map.keys input)) 24 | print (maximumHappiness input people1) 25 | 26 | -- Adding the extra person as the empty string, it's definitely not in the list 27 | let people2 = "" : people1 28 | print (maximumHappiness input people2) 29 | 30 | neighbors :: [String] -> [Edge] 31 | neighbors [] = [] 32 | neighbors (x:xs) = zipWith edge (x:xs) (xs ++ [x]) 33 | 34 | maximumHappiness :: 35 | Map Edge Int {- ^ Happiness effects of each edge -} -> 36 | [String] {- ^ List of all people to be seated -} -> 37 | Int {- ^ Maximum happiness effect -} 38 | maximumHappiness relationships people = maximum (score <$> permutations people) 39 | where 40 | score xs = sum [Map.findWithDefault 0 e relationships | e <- neighbors xs] 41 | 42 | loadInput :: IO (Map Edge Int) 43 | loadInput = Map.fromListWith (+) . map parseLine . lines <$> readFile "input13.txt" 44 | 45 | parseLine :: String -> (Edge, Int) 46 | parseLine str = 47 | case words (filter (/='.') str) of 48 | [a,_,"gain",n,_,_,_,_,_,_,b] -> (edge a b, read n) 49 | [a,_,"lose",n,_,_,_,_,_,_,b] -> (edge a b, - read n) 50 | _ -> error ("Bad input line: " ++ str) 51 | 52 | uniques :: Ord a => [a] -> [a] 53 | uniques = Set.toList . Set.fromList 54 | -------------------------------------------------------------------------------- /Day14.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Data.List 4 | 5 | data Reindeer = Reindeer 6 | { speed :: Int -- ^ units of distance flown per second 7 | , stamina :: Int -- ^ number of seconds flown before rest 8 | , breaktime :: Int -- ^ number of seconds rested before flying 9 | } 10 | 11 | main :: IO () 12 | main = 13 | do rs <- loadInput 14 | let race = map (take 2503 . positions) rs 15 | print (maximum (map last race)) 16 | print (maximum (scores race)) 17 | 18 | loadInput :: IO [Reindeer] 19 | loadInput = map parseLine . lines <$> readFile "input14.txt" 20 | 21 | parseLine :: String -> Reindeer 22 | parseLine str = 23 | case words str of 24 | [_, _, _, n, _, _, m, _, _, _, _, _, _, o, _] -> 25 | Reindeer { speed = read n 26 | , stamina = read m 27 | , breaktime = read o 28 | } 29 | _ -> error str 30 | 31 | -- | Compute the position of each reindeer at each second of the race 32 | positions :: Reindeer -> [Int] 33 | positions r 34 | = partialSums 35 | $ cycle 36 | $ replicate (stamina r) (speed r) ++ replicate (breaktime r) 0 37 | 38 | -- | Given a list of race positions return a list of scores 39 | scores :: [[Int]] -> [Int] 40 | scores = map sum . transpose . map awardPoints . transpose 41 | 42 | -- | Map each position to 1 point if it's in the lead or 0 otherwise 43 | awardPoints :: 44 | [Int] {- ^ positions -} -> 45 | [Int] {- ^ points -} 46 | awardPoints posns = [ if p == best then 1 else 0 | p <- posns ] 47 | where 48 | best = maximum posns 49 | 50 | -- | Partial sums starting with first element. 51 | -- 52 | -- > paritalSums [1..5] 53 | -- [1,3,6,10,15] 54 | partialSums :: Num a => [a] -> [a] 55 | partialSums [] = [] 56 | partialSums xs = scanl1 (+) xs 57 | -------------------------------------------------------------------------------- /Day15.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Data.List 4 | 5 | main :: IO () 6 | main = 7 | do input <- loadInput 8 | 9 | let n = fromIntegral (length input) 10 | possibilities = computeStats input <$> divisions n 100 11 | 12 | print (maximum (map score possibilities)) 13 | print (maximum [score meal | meal <- possibilities, last meal == 500]) 14 | 15 | score :: 16 | [Integer] {- ^ properties list, calories are last -} -> 17 | Integer {- ^ score for recipe -} 18 | score = product . init 19 | 20 | computeStats :: 21 | [[Integer]] {- ^ properties for all ingredients -} -> 22 | [Integer] {- ^ divisions -} -> 23 | [Integer] {- ^ cumulative properties -} 24 | computeStats props divs 25 | = map (max 0 . sum) -- compute sum of each property 26 | $ transpose -- compute lists of each property 27 | $ zipWith (map . (*)) divs props -- scale up properties by ingredient 28 | 29 | divisions :: 30 | Integer {- ^ number of divisions -} -> 31 | Integer {- ^ amount to divide -} -> 32 | [[Integer]] {- ^ all possible divisions -} 33 | divisions 1 n = [[n]] 34 | divisions cnt n = 35 | do x <- [1..n-cnt+1] 36 | xs <- divisions (cnt - 1) (n-x) 37 | return (x:xs) 38 | 39 | parseLine :: String -> [Integer] 40 | parseLine = map read . everyOther . drop 1 . words . filter (/=',') 41 | 42 | everyOther :: [a] -> [a] 43 | everyOther (_:x:xs) = x : everyOther xs 44 | everyOther _ = [] 45 | 46 | loadInput :: IO [[Integer]] 47 | loadInput = map parseLine . lines <$> readFile "input15.txt" 48 | -------------------------------------------------------------------------------- /Day16.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Data.Char (isPunctuation) 4 | 5 | main :: IO () 6 | main = 7 | do input <- loadInput 8 | print [lookup "Sue" props | props <- input, matchesClues1 props] 9 | print [lookup "Sue" props | props <- input, matchesClues2 props] 10 | 11 | matchesClues1 :: [(String,Int)] -> Bool 12 | matchesClues1 = matcher (const (==)) 13 | 14 | matchesClues2 :: [(String,Int)] -> Bool 15 | matchesClues2 = 16 | matcher $ \prop -> 17 | case prop of 18 | "cats" -> (<) 19 | "trees" -> (<) 20 | "pomeranians" -> (>) 21 | "goldfish" -> (>) 22 | _ -> (==) 23 | 24 | matcher :: (String -> Int -> Int -> Bool) -> [(String,Int)] -> Bool 25 | matcher match = all $ \(prop,memory) -> 26 | case lookup prop clues of 27 | Nothing -> True 28 | Just mfcsam -> match prop mfcsam memory 29 | 30 | clues :: [(String,Int)] 31 | clues = parseLine 32 | " children : 3 \ 33 | \ cats : 7 \ 34 | \ samoyeds : 2 \ 35 | \ pomeranians: 3 \ 36 | \ akitas : 0 \ 37 | \ vizslas : 0 \ 38 | \ goldfish : 5 \ 39 | \ trees : 3 \ 40 | \ cars : 2 \ 41 | \ perfumes : 1 " 42 | 43 | loadInput :: IO [[(String,Int)]] 44 | loadInput = map parseLine . lines <$> readFile "input16.txt" 45 | 46 | parseLine :: String -> [(String,Int)] 47 | parseLine = asProps . words . filter (not . isPunctuation) 48 | 49 | asProps :: [String] -> [(String,Int)] 50 | asProps [] = [] 51 | asProps (x:y:z) = (x,read y) : asProps z 52 | asProps [_] = error "props mismatched" 53 | -------------------------------------------------------------------------------- /Day17.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Data.Array 4 | import Data.List 5 | import Data.Maybe 6 | 7 | main :: IO () 8 | main = 9 | do input <- loadInput 10 | let combos = combinations input 150 11 | print (sum combos) 12 | print (fromMaybe 0 (find (/=0) combos)) 13 | 14 | loadInput :: IO [Int] 15 | loadInput = map read . words <$> readFile "input17.txt" 16 | 17 | -- | Given a list of container sizes and an amount, 18 | -- return a list of the ways to chose a subset of those containers 19 | -- so that they sum to the desired amount. The resulting list 20 | -- is arranged by number of containers used. The nth element uses 21 | -- n-containers (zero-indexed). 22 | combinations :: [Int] -> Int -> [Int] 23 | combinations sizes amount = [ t ! (amount, n, i) | i <- [0..n] ] 24 | where 25 | n = length sizes 26 | sizeArray = listArray (1,n) sizes 27 | 28 | bnds = ( (0,0,0) , (amount, n, n) ) 29 | t = array bnds [ (i, ways i) | i <- range bnds ] 30 | 31 | ways :: (Int,Int,Int) -> Int 32 | ways (amt, sizeIx, containers) 33 | 34 | -- Success, you can fit no eggnog into no containers! 35 | | amt == 0 && containers == 0 = 1 36 | 37 | -- Failure, ran out of containers or didn't enough enough containers 38 | | amt == 0 || sizeIx == 0 || containers == 0 = 0 39 | 40 | -- This container doesn't fit, try the next one 41 | | amt < containerSize = t ! (amt, sizeIx - 1, containers) 42 | 43 | -- This container works, let's try with it and without it 44 | | otherwise = t ! (amt , sizeIx - 1, containers ) 45 | + t ! (amt - containerSize, sizeIx - 1, containers - 1) 46 | where 47 | containerSize = sizeArray ! sizeIx 48 | -------------------------------------------------------------------------------- /Day18.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Data.Array.Unboxed 4 | 5 | type Lights = UArray (Int,Int) Bool 6 | 7 | main :: IO () 8 | main = 9 | do input <- loadInput 10 | let steps = 100 11 | print $ countLights $ iterate (applyRule life) input !! steps 12 | print $ countLights $ iterate (applyRule (addCorners life)) input !! steps 13 | 14 | countLights :: Lights -> Int 15 | countLights = length . filter id . elems 16 | 17 | loadInput :: IO Lights 18 | loadInput = 19 | do str <- readFile "input18.txt" 20 | let lights = map (map (=='#')) (lines str) 21 | return $! case lights of 22 | [] -> array ((1,1),(0,0)) [] 23 | x:_ -> array ((1,1),(length lights, length x)) 24 | [ ((r,c), col) 25 | | (r,row) <- zip [1..] lights 26 | , (c,col) <- zip [1..] row ] 27 | 28 | type Rule = Lights -> (Int,Int) -> Bool 29 | 30 | applyRule :: Rule -> Lights -> Lights 31 | applyRule f a = array (bounds a) [ (i, f a i) | i <- range (bounds a) ] 32 | 33 | life :: Rule 34 | life a i@(x,y) = neighbors == 3 || 35 | neighbors == 2 && a!i 36 | where 37 | neighbors = length [ () | x' <- [x-1..x+1], y' <- [y-1..y+1] 38 | , let i' = (x',y') 39 | , i /= i' 40 | , inRange (bounds a) i' 41 | , a ! i' 42 | ] 43 | 44 | addCorners :: Rule -> Rule 45 | addCorners f a i@(x,y) 46 | | x == xlo || x == xhi 47 | , y == ylo || y == yhi = True 48 | | otherwise = f a i 49 | where 50 | ((xlo,ylo),(xhi,yhi)) = bounds a 51 | -------------------------------------------------------------------------------- /Day19.hs: -------------------------------------------------------------------------------- 1 | module Main (main) where 2 | 3 | import Data.Array 4 | import Data.Char 5 | import Data.Map ( Map ) 6 | import Data.Maybe 7 | import qualified Data.Map.Strict as Map 8 | import qualified Data.Set as Set 9 | 10 | newtype Atom = Atom String 11 | deriving (Eq,Ord) 12 | 13 | main :: IO () 14 | main = 15 | do (rules, input) <- loadInput 16 | print (minRulesNeeded rules input (Atom "e")) 17 | 18 | loadInput :: IO ( Map Atom [[Atom]], [Atom] ) 19 | loadInput = 20 | do xs <- lines <$> readFile "input19.txt" 21 | return $! case break null xs of 22 | (rules, ["", initial]) -> (toMap (parseRule <$> rules), parseMolecule initial) 23 | _ -> error "Bad input" 24 | 25 | toMap :: Ord k => [(k,v)] -> Map k [v] 26 | toMap = Map.fromListWith (++) . map (fmap pure) 27 | 28 | -- | Add empty elements to the map so that every @a@ that occurs in 29 | -- the values of the map also occurs in the keys. 30 | extendRules :: Ord a => Map a [[a]] -> Map a [[a]] 31 | extendRules rules = Map.unionWith (++) extraRules rules 32 | where 33 | extraRules = Map.fromSet (const []) 34 | $ Set.fromList (concat (concat (Map.elems rules))) 35 | 36 | -- | 37 | -- > parseRule "A => BC" 38 | -- (Atom "A", [Atom "B", Atom "C"]) 39 | parseRule :: String -> (Atom, [Atom]) 40 | parseRule str = 41 | case words str of 42 | [x,"=>",y] -> (Atom x,parseMolecule y) 43 | _ -> error ("Bad line: " ++ str) 44 | 45 | -- | 46 | -- > parseMolecule "AbCdEF" 47 | -- [Atom "Ab", Atom "Cd", Atom "E", Atom "F"] 48 | parseMolecule :: String -> [Atom] 49 | parseMolecule str = 50 | case str of 51 | "" -> [] 52 | x:xs -> case break isUpper xs of 53 | (y,ys) -> Atom (x:y) : parseMolecule ys 54 | 55 | -- | Given a map of rewrite rules rewriting the keys to any of the 56 | -- alternatives, return the minimum number of rewrites needed to rewrite 57 | -- the start symbol into the input. 58 | minRulesNeeded :: 59 | Ord a => 60 | Map a [[a]] {- ^ rules, sum of products -} -> 61 | [a] {- ^ input -} -> 62 | a {- ^ start state -} -> 63 | Maybe Int 64 | minRulesNeeded rules input start = minRulesNeededInt ruleArr inputArr (toInt start) 65 | where 66 | rules' = extendRules rules 67 | toInt x = Map.findIndex x rules' 68 | 69 | numRules = Map.size rules' 70 | numInput = length input 71 | inputArr = listArray (0,numInput-1) (map toInt input) 72 | ruleArr = listArray (0,numRules-1) (Map.elems (fmap (map (map toInt)) rules')) 73 | 74 | -- | Given an array of inputs determine how many rule applications 75 | -- are required to transform the start state into the input. 76 | -- 77 | -- This solution uses dynamic programming. The solutions are memoized 78 | -- as about how many steps, if any, each substring of the input takes to 79 | -- match each of the symbols in the alphabet. 80 | minRulesNeededInt :: 81 | Ix i => 82 | Array i [[i]] {- ^ rules, sum of products -} -> 83 | Array Int i {- ^ input -} -> 84 | i {- ^ start -} -> 85 | Maybe Int {- ^ minimum rules needed -} 86 | minRulesNeededInt rules input = cost inputLo inputHi 87 | where 88 | (inputLo,inputHi) = bounds input 89 | (rulesLo,rulesHi) = bounds rules 90 | costBounds = ((inputLo,inputLo,rulesLo) 91 | ,(inputHi,inputHi,rulesHi)) 92 | 93 | cost start end rule = costArray ! (start,end,rule) 94 | 95 | costArray = generate costBounds cost' 96 | 97 | cost' (start,end,ruleIx) 98 | | start == end, input ! start == ruleIx = Just 0 99 | | otherwise = fmap succ 100 | $ minimum' 101 | $ mapMaybe (nonTerm start end) 102 | $ rules ! ruleIx 103 | 104 | nonTerm start end rhs = 105 | case rhs of 106 | [] -> Nothing 107 | [x] -> cost start end x 108 | x:xs -> minimum' 109 | [ cost1 + cost2 110 | | mid <- [start .. end - length xs] 111 | , cost1 <- maybeToList (cost start mid x) 112 | , cost2 <- maybeToList (nonTerm (succ mid) end xs) 113 | ] 114 | 115 | -- | Generate an array given the bounds an a function from indexes to elements. 116 | generate :: Ix i => (i,i) -> (i -> e) -> Array i e 117 | generate bnd f = array bnd [ (i, f i) | i <- range bnd ] 118 | 119 | -- | Returns the minimum element of a list unless the list is empty. 120 | minimum' :: Ord a => [a] -> Maybe a 121 | minimum' [] = Nothing 122 | minimum' xs = Just $! minimum xs 123 | -------------------------------------------------------------------------------- /Day2.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Data.List 4 | import Data.List.Split 5 | import Text.Read 6 | 7 | data Package = Package Int Int Int 8 | data Face = Face Int Int 9 | 10 | main :: IO () 11 | main = 12 | do packages <- loadInput 13 | print (sum (part1 <$> packages)) 14 | print (sum (part2 <$> packages)) 15 | 16 | loadInput :: IO [Package] 17 | loadInput = map parseLine . lines <$> readFile "input2.txt" 18 | 19 | parseLine :: String -> Package 20 | parseLine str = 21 | case traverse readMaybe (splitOn "x" str) of 22 | Just [x,y,z] -> Package x y z 23 | _ -> error ("bad line: " ++ str) 24 | 25 | part1 :: Package -> Int 26 | part1 p = surfaceArea p + area (smallestFace p) 27 | 28 | part2 :: Package -> Int 29 | part2 p = volume p + perimeter (smallestFace p) 30 | 31 | volume :: Package -> Int 32 | volume (Package x y z) = x*y*z 33 | 34 | surfaceArea :: Package -> Int 35 | surfaceArea (Package x y z) = 2 * (x*y + x*z + y*z) 36 | 37 | smallestFace :: Package -> Face 38 | smallestFace (Package x y z) = let a:b:_ = sort [x,y,z] in Face a b 39 | 40 | area :: Face -> Int 41 | area (Face x y) = x*y 42 | 43 | perimeter :: Face -> Int 44 | perimeter (Face x y) = 2*(x+y) 45 | -------------------------------------------------------------------------------- /Day20.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Data.Array.Unboxed (UArray, assocs, accumArray) 4 | import Data.List (find) 5 | 6 | main :: IO () 7 | main = 8 | do print (findHouse solve1) 9 | print (findHouse solve2) 10 | 11 | findHouse :: UArray Int Int -> Maybe Int 12 | findHouse = fmap fst . find (\x -> snd x >= target) . assocs 13 | 14 | target :: Int 15 | target = 36000000 16 | 17 | solve1 :: UArray Int Int 18 | solve1 = 19 | let top = target `quot` 10 in 20 | accumArray (+) 0 (1,top) 21 | [ (house, elf * 10) 22 | | elf <- [1..top] 23 | , house <- [elf, elf+elf .. top] 24 | ] 25 | 26 | solve2 :: UArray Int Int 27 | solve2 = 28 | let top = target `quot` 11 in 29 | accumArray (+) 0 (1,top) 30 | [ (house, elf*11) 31 | | elf <- [1..top] 32 | , house <- [elf, elf+elf .. min top (elf*50)] 33 | ] 34 | -------------------------------------------------------------------------------- /Day21.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Data.List 4 | import Data.Ord 5 | 6 | data Item = Item { itemName :: String, itemCost, itemDamage, itemArmor :: Int } 7 | deriving (Show, Read) 8 | 9 | main = 10 | do print $ minimumBy (comparing itemCost) 11 | $ filter fight 12 | $ gearOptions 13 | print $ maximumBy (comparing itemCost) 14 | $ filter (not . fight) 15 | $ gearOptions 16 | 17 | emptyItem :: String -> Item 18 | emptyItem name = Item name 0 0 0 19 | 20 | --Weapons: Cost Damage Armor 21 | weapons :: [Item] 22 | weapons = 23 | [ Item "Dagger" 8 4 0 24 | , Item "Shortsword" 10 5 0 25 | , Item "Warhammer" 25 6 0 26 | , Item "Longsword" 40 7 0 27 | , Item "Greataxe" 74 8 0 28 | ] 29 | 30 | --Armor: Cost Damage Armor 31 | armors :: [Item] 32 | armors = 33 | [ Item "Leather" 13 0 1 34 | , Item "Chainmail" 31 0 2 35 | , Item "Splintmail" 53 0 3 36 | , Item "Bandedmail" 75 0 4 37 | , Item "Platemail" 102 0 5 38 | ] 39 | 40 | -- Rings: Cost Damage Armor 41 | rings :: [Item] 42 | rings = 43 | [ Item "Damage +1" 25 1 0 44 | , Item "Damage +2" 50 2 0 45 | , Item "Damage +3" 100 3 0 46 | , Item "Defense +1" 20 0 1 47 | , Item "Defense +2" 40 0 2 48 | , Item "Defense +3" 80 0 3 49 | ] 50 | 51 | combine :: Item -> Item -> Item 52 | combine x y = Item 53 | { itemName = itemName x ++ " and " ++ itemName y 54 | , itemCost = itemCost x + itemCost y 55 | , itemDamage = itemDamage x + itemDamage y 56 | , itemArmor = itemArmor x + itemArmor y 57 | } 58 | 59 | gearOptions :: [Item] 60 | gearOptions = 61 | do weapon <- weapons 62 | armor <- emptyItem "unarmored" : armors 63 | ring <- chooseUpTo 2 rings 64 | return (foldl1 combine (weapon : armor : ring)) 65 | 66 | chooseUpTo 0 _ = [[]] 67 | chooseUpTo _ [] = [[]] 68 | chooseUpTo n (x:xs) = map (x:) (chooseUpTo (n-1) xs) ++ chooseUpTo n xs 69 | 70 | fight gear = outcome 100 (max 1 (8 - itemArmor gear)) 104 (max 1 (itemDamage gear - 1)) 71 | 72 | outcome :: 73 | Int -> Int -> 74 | Int -> Int -> 75 | Bool 76 | outcome hp1 dec1 hp2 dec2 = (hp1-1)`quot`dec1 >= (hp2-1)`quot`dec2 77 | -------------------------------------------------------------------------------- /Day22.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Control.Monad 4 | import Data.List 5 | import qualified Data.IntMap as IntMap 6 | import Data.IntMap ( IntMap ) 7 | 8 | main :: IO () 9 | main = 10 | do print (runSim initialState) 11 | print (runSim initialState { difficulty = 1 }) 12 | 13 | runSim :: GameState -> Int 14 | runSim s = search (IntMap.singleton 0 [s]) maxBound 15 | 16 | data Spell = Recharge | Poison | Shield | Drain | MagicMissile 17 | deriving Eq 18 | 19 | spellDamage :: Spell -> Int 20 | spellDamage spell = 21 | case spell of 22 | MagicMissile -> 4 23 | Drain -> 2 24 | _ -> 0 25 | 26 | spellHeal :: Spell -> Int 27 | spellHeal spell = 28 | case spell of 29 | Drain -> 2 30 | _ -> 0 31 | 32 | spellCost :: Spell -> Int 33 | spellCost s = 34 | case s of 35 | Recharge -> 229 36 | Poison -> 173 37 | Shield -> 113 38 | Drain -> 73 39 | MagicMissile -> 53 40 | 41 | 42 | data GameState = GameState 43 | { manaPool 44 | , manaSpent 45 | , poisonTimer 46 | , rechargeTimer 47 | , shieldTimer 48 | , playerHp 49 | , bossHp, bossDamage, difficulty :: !Int 50 | } 51 | deriving (Eq, Show) 52 | 53 | initialState :: GameState 54 | initialState = GameState 55 | { manaPool = 500 56 | , manaSpent = 0 57 | , poisonTimer = 0 58 | , rechargeTimer = 0 59 | , shieldTimer = 0 60 | , playerHp = 50 61 | , bossHp = 51 62 | , bossDamage = 9 63 | , difficulty = 0 64 | } 65 | 66 | stepTimers :: GameState -> GameState 67 | stepTimers s = s 68 | { manaPool = manaPool s + 69 | if rechargeTimer s > 0 then 101 else 0 70 | , bossHp = bossHp s - 71 | if poisonTimer s > 0 then 3 else 0 72 | , poisonTimer = dec (poisonTimer s) 73 | , rechargeTimer = dec (rechargeTimer s) 74 | , shieldTimer = dec (shieldTimer s) 75 | } 76 | 77 | bossAttack :: GameState -> GameState 78 | bossAttack s = s { playerHp = playerHp s - effectiveAttack } 79 | where 80 | effectiveAttack = max 1 (bossDamage s - armor) 81 | armor | shieldTimer s > 0 = 7 82 | | otherwise = 0 83 | 84 | applyDifficulty :: GameState -> GameState 85 | applyDifficulty s = s { playerHp = playerHp s - difficulty s } 86 | 87 | advance :: GameState -> [GameState] 88 | advance s = 89 | stepTimers (applyDifficulty s) --> \s1 -> 90 | availableSpells s1 >>= \spell -> 91 | stepTimers (applySpell spell s1) --> \s2 -> 92 | bossAttack s2 --> \s3 -> 93 | return s3 94 | 95 | infixl 1 --> 96 | 97 | (-->) :: GameState -> (GameState -> [GameState]) -> [GameState] 98 | s --> k 99 | | playerDead s = [] 100 | | bossDead s = [s] 101 | | otherwise = k s 102 | 103 | applySpell :: Spell -> GameState -> GameState 104 | applySpell spell s = 105 | s { manaSpent = manaSpent s + spellCost spell 106 | , manaPool = manaPool s - spellCost spell 107 | , rechargeTimer = if spell == Recharge then 5 else rechargeTimer s 108 | , poisonTimer = if spell == Poison then 6 else poisonTimer s 109 | , shieldTimer = if spell == Shield then 6 else shieldTimer s 110 | , bossHp = bossHp s - spellDamage spell 111 | , playerHp = playerHp s + spellHeal spell 112 | } 113 | 114 | availableSpells :: GameState -> [Spell] 115 | availableSpells s = 116 | filter (\spell -> spellCost spell <= manaPool s) 117 | $ [Poison | poisonTimer s == 0] 118 | ++ [Recharge | rechargeTimer s == 0] 119 | ++ [Shield | shieldTimer s == 0] 120 | ++ [MagicMissile, Drain] 121 | 122 | dec :: Int -> Int 123 | dec x | x <= 1 = 0 124 | dec x = x-1 125 | 126 | -- Search the frontier of possible game states for the minimum possible mana 127 | -- needed to kill a boss. The frontier is advanced by stepping one full turn 128 | -- for each state picking the states with the minimum mana used so far. 129 | -- Once the best seen so far is as good as the best states in the frontier 130 | -- we know we're done because mana spending is monotonic. 131 | search :: 132 | IntMap [GameState] {- ^ search frontier indexed by mana spent -} -> 133 | Int {- ^ lowest mana used to kill boss so far -} -> 134 | Int {- ^ lowest possible mana used to kill boss -} 135 | search states best = 136 | case IntMap.minViewWithKey states of 137 | Nothing -> best 138 | Just ((k,ss),states') 139 | | best <= k -> best 140 | | otherwise -> search (foldl' schedule states' nextss) best' 141 | where 142 | nextss = nub (concatMap advance ss) 143 | best' = minimum (best : map manaSpent (filter bossDead nextss)) 144 | 145 | schedule m t = IntMap.insertWith (++) (manaSpent t) [t] m 146 | 147 | bossDead :: GameState -> Bool 148 | bossDead s = bossHp s <= 0 149 | 150 | playerDead :: GameState -> Bool 151 | playerDead s = playerHp s <= 0 152 | -------------------------------------------------------------------------------- /Day23.hs: -------------------------------------------------------------------------------- 1 | {-# Language TemplateHaskell #-} 2 | module Main (main) where 3 | 4 | import Language.Haskell.TH 5 | import Day23TH 6 | 7 | program :: Int -> Int -> Int 8 | program = $(compile =<< runIO loadInput) 9 | 10 | main :: IO () 11 | main = 12 | do print (program 0 0) 13 | print (program 1 0) 14 | -------------------------------------------------------------------------------- /Day23TH.hs: -------------------------------------------------------------------------------- 1 | {-# Language BangPatterns #-} 2 | {-# Language TemplateHaskell #-} 3 | module Day23TH where 4 | 5 | import Data.Char 6 | import Data.Array 7 | import Language.Haskell.TH 8 | 9 | data Instr 10 | = Half Register 11 | | Triple Register 12 | | Increment Register 13 | | Copy Int Register 14 | | Jump Int 15 | | JumpIfEven Register Int 16 | | JumpIfOne Register Int 17 | deriving Show 18 | 19 | data Register = A | B 20 | deriving Show 21 | 22 | toArray :: [a] -> Array Int a 23 | toArray xs = listArray (1,length xs) xs 24 | 25 | parseLine :: String -> Instr 26 | parseLine str = 27 | case words (filter (\x -> isAlphaNum x || x == '-' || x == ' ') str) of 28 | ["hlf",r] -> Half (parseRegister r) 29 | ["tpl",r] -> Triple (parseRegister r) 30 | ["inc",r] -> Increment (parseRegister r) 31 | ["jmp",o] -> Jump (read o) 32 | ["cpy",r,o] -> Copy (read o) (parseRegister o) 33 | ["jie",r,o] -> JumpIfEven (parseRegister r) (read o) 34 | ["jio",r,o] -> JumpIfOne (parseRegister r) (read o) 35 | _ -> error str 36 | 37 | parseRegister :: String -> Register 38 | parseRegister "a" = A 39 | parseRegister "b" = B 40 | parseRegister r = error ("Not register: " ++ r) 41 | 42 | loadInput :: IO (Array Int Instr) 43 | loadInput = toArray . map parseLine . lines <$> readFile "input23.txt" 44 | 45 | compile :: Array Int Instr -> ExpQ 46 | compile program = 47 | do names <- traverse (\_ -> newName "label") program 48 | let start = names ! fst (bounds names) 49 | letE [ valD (varP (names ! pc)) 50 | (normalB (compile1 pc names instr)) 51 | [] 52 | | (pc,instr) <- assocs program ] 53 | [| $(varE start) :: Int -> Int -> Int |] 54 | 55 | (!?) :: Ix i => Array i e -> i -> Maybe e 56 | a !? i 57 | | inRange (bounds a) i = Just $! a ! i 58 | | otherwise = Nothing 59 | 60 | compile1 :: Int -> Array Int Name -> Instr -> ExpQ 61 | compile1 pc names instr = 62 | let run o = maybe [| \a b -> b |] varE (names !? (pc+o)) 63 | step = run 1 64 | in case instr of 65 | Half A -> [| \a b -> $step (a`quot`2) b |] 66 | Half B -> [| \a b -> $step a (b`quot`2) |] 67 | Triple A -> [| \a b -> $step (3*a) b |] 68 | Triple B -> [| \a b -> $step a (3*b) |] 69 | Increment A -> [| \a b -> $step (a+1) b |] 70 | Increment B -> [| \a b -> $step a (b+1) |] 71 | Jump o -> run o 72 | JumpIfEven A o -> [| \a b -> if even a then $(run o) a b else $step a b |] 73 | JumpIfEven B o -> [| \a b -> if even b then $(run o) a b else $step a b |] 74 | JumpIfOne A o -> [| \a b -> if a == 1 then $(run o) a b else $step a b |] 75 | JumpIfOne B o -> [| \a b -> if b == 1 then $(run o) a b else $step a b |] 76 | -------------------------------------------------------------------------------- /Day24.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Data.List 4 | import Data.Maybe 5 | import Data.Monoid 6 | import Data.Ord 7 | import Data.Foldable 8 | 9 | data Packages = Packages { pkgSum, pkgCount, pkgProduct :: !Int } 10 | deriving (Eq, Show) 11 | 12 | noPackages :: Packages 13 | noPackages = Packages 14 | { pkgCount = 0 15 | , pkgSum = 0 16 | , pkgProduct = 1 17 | } 18 | 19 | addPackage :: Int -> Packages -> Packages 20 | addPackage p pkgs = Packages 21 | { pkgCount = pkgCount pkgs + 1 22 | , pkgSum = pkgSum pkgs + p 23 | , pkgProduct = fromIntegral p * pkgProduct pkgs 24 | } 25 | 26 | instance Ord Packages where 27 | compare = comparing pkgCount <> comparing pkgProduct <> comparing pkgSum 28 | 29 | loadInput :: IO [Int] 30 | loadInput = map read . lines <$> readFile "input24.txt" 31 | 32 | search :: Int -> [Int] -> Maybe Int 33 | search n ps0 = listToMaybe $ 34 | do (pkg,ps1) <- sortBy (comparing fst) (start ps0) 35 | moreGroups (n-1) ps1 36 | return (pkgProduct pkg) 37 | 38 | where 39 | goal = sum ps0 `quot` n 40 | 41 | moreGroups 1 _ = [()] 42 | moreGroups i ps1 = 43 | do (_,ps2) <- start ps1 44 | moreGroups (i-1) ps2 45 | 46 | start = aux noPackages [] . sort 47 | 48 | aux :: Packages -> [Int] -> [Int] -> [(Packages,[Int])] 49 | aux a qs _ | pkgSum a == goal = [(a,qs)] 50 | aux _ _ [] = [] 51 | aux a _ (p:_) | pkgSum (addPackage p a) > goal = [] 52 | aux a qs (p:ps) = aux (addPackage p a) qs ps 53 | ++ aux a (p:qs) ps 54 | 55 | main :: IO () 56 | main = 57 | do input <- loadInput 58 | print (search 3 input) 59 | print (search 4 input) 60 | -------------------------------------------------------------------------------- /Day25.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import GHC.Integer.GMP.Internals (powModInteger) 4 | 5 | main :: IO () 6 | main = print (code 3010 3019) 7 | 8 | code :: 9 | Integer {- ^ row -} -> 10 | Integer {- ^ column -} -> 11 | Integer 12 | code row col 13 | = 20151125 14 | * powModInteger 252533 (cell (row-1) (col-1)) 33554393 15 | `mod` 33554393 16 | 17 | -- | Compute zero-indexed cell of diagonally filled table using zero-indexed row, column. 18 | cell :: 19 | Integer {- ^ row -} -> 20 | Integer {- ^ column -} -> 21 | Integer 22 | cell r c = sum1N (r+c) + c 23 | 24 | -- | Compute sum of non-negative integers from 0 to the given upper bound. 25 | sum1N :: Integer {- ^ upper bound -} -> Integer 26 | sum1N n = n*(n+1)`quot`2 27 | -------------------------------------------------------------------------------- /Day3.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Data.List 4 | import Data.List.Split 5 | import qualified Data.Set as Set 6 | 7 | data Dir = U | D | L | R deriving (Read,Show,Ord,Eq) 8 | 9 | data Loc = Loc !Int !Int deriving (Read,Show,Ord,Eq) 10 | 11 | origin :: Loc 12 | origin = Loc 0 0 13 | 14 | main :: IO () 15 | main = 16 | do directions <- loadInput 17 | print (countHouses 1 directions) 18 | print (countHouses 2 directions) 19 | 20 | countHouses :: Int {- ^ workers -} -> [Dir] -> Int 21 | countHouses n 22 | = cardinality . concatMap (scanl' step origin) . transpose . chunksOf n 23 | 24 | cardinality :: Ord a => [a] -> Int 25 | cardinality = Set.size . Set.fromList 26 | 27 | step :: Loc -> Dir -> Loc 28 | step (Loc x y) dir = 29 | case dir of 30 | U -> Loc x (y+1) 31 | D -> Loc x (y-1) 32 | L -> Loc (x-1) y 33 | R -> Loc (x+1) y 34 | 35 | loadInput :: IO [Dir] 36 | loadInput = map parseChar <$> readFile "input3.txt" 37 | 38 | parseChar :: Char -> Dir 39 | parseChar c = 40 | case c of 41 | '^' -> U 42 | 'v' -> D 43 | '<' -> L 44 | '>' -> R 45 | _ -> error ("Bad input character: " ++ [c]) 46 | -------------------------------------------------------------------------------- /Day4.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Control.Monad (replicateM) 4 | import Data.Binary.Get (runGet, getWord32le) 5 | import Data.Bits ((.|.), (.&.), complement, rotateL, xor) 6 | import Data.ByteString.Builder (Builder, toLazyByteString, lazyByteString, word8, word32LE, word64LE) 7 | import Data.ByteString.Builder.Extra (untrimmedStrategy, toLazyByteStringWith) 8 | import Data.Int (Int64) 9 | import Data.List (find, foldl', zipWith3) 10 | import Data.Monoid ((<>)) 11 | import Data.Vector (Vector) 12 | import Data.Word (Word32) 13 | import qualified Data.ByteString.Lazy as L 14 | import qualified Data.ByteString.Lazy.Char8 as L8 15 | import qualified Data.Vector as Vector 16 | 17 | main :: IO () 18 | main = 19 | do [key] <- words <$> readFile "input4.txt" 20 | print (solve key 5) 21 | print (solve key 6) 22 | 23 | -- | Find the smallest, positive integer that has the specified 24 | -- number of leading zeros in its hex representation. 25 | solve :: String -> Int64 -> Maybe Int 26 | solve key n = find (zeros n . adventHash key) [1..] 27 | 28 | -- | The "advent hash" of a number is the MD5 digest of a key string 29 | -- and a ASCII, base-10 representation of the number. 30 | adventHash :: 31 | String {- ^ player key -} -> 32 | Int {- ^ number to hash -} -> 33 | L.ByteString 34 | adventHash key i = md5 (L8.pack (key ++ show i)) 35 | 36 | -- | Test that the first @n@ digits in hex-representation of 37 | -- the digest are @0@. 38 | zeros :: Int64 -> L.ByteString -> Bool 39 | zeros n bs = L.all (==0) (L.take n2 bs) 40 | && (even n || L.index bs n2 < 0x10) 41 | where 42 | n2 = n`quot`2 43 | 44 | data Context = Context !Word32 !Word32 !Word32 !Word32 45 | 46 | -- > md5 "" 47 | -- d41d8cd98f00b204e9800998ecf8427e 48 | -- 49 | -- > md5 "The quick brown fox jumps over the lazy dog." 50 | -- e4d909c290d0fb1ca068ffaddf22cbd0 51 | md5 :: L.ByteString -> L.ByteString 52 | md5 = finish . foldl' addBlock initialState . toBlocks . envelope 53 | 54 | -- | Extract the final MD5 digest from a context 55 | finish :: Context -> L.ByteString 56 | finish (Context a b c d) 57 | = toFixedByteString 16 58 | $ word32LE a <> word32LE b <> word32LE c <> word32LE d 59 | 60 | -- | Pad out an input string to be suitable for breaking into 61 | -- blocks for MD5. This algorithm pads with a @1@ and then 62 | -- as many @0@ bytes as needed so that when the 8-byte length 63 | -- is added that the whole message's length is a multiple of 64 | -- 64-bytes. 65 | envelope :: L.ByteString -> L.ByteString 66 | envelope xs = toLazyByteString 67 | $ lazyByteString xs 68 | <> word8 0x80 -- 0b10000000 69 | <> lazyByteString (L.replicate padLen 0) 70 | <> word64LE (fromIntegral bitLen) 71 | where 72 | padLen = (55 - L.length xs) `mod` 64 73 | bitLen = 8 * L.length xs 74 | 75 | -- | Break a bytestring with a length that is a multiple of 64 76 | -- into blocks of 16 32-bit words loaded in little-endian order. 77 | toBlocks :: L.ByteString -> [Vector Word32] 78 | toBlocks 79 | = map (Vector.fromList . runGet (replicateM 16 getWord32le)) 80 | . takeWhile (not . L.null) 81 | . iterate (L.drop 64) 82 | 83 | -- | Point-wise addition of the components of a 'Context' 84 | addState :: Context -> Context -> Context 85 | addState (Context a b c d) (Context w x y z) = Context (a+w) (b+x) (c+y) (d+z) 86 | 87 | addBlock :: 88 | Context -> 89 | Vector Word32 {- ^ message chunk, 16 elements -} -> 90 | Context 91 | addBlock st m 92 | = addState st 93 | $ applyRounds m4 rs4 94 | $ applyRounds m3 rs3 95 | $ applyRounds m2 rs2 96 | $ applyRounds m1 rs1 97 | $ st 98 | where 99 | applyRounds mix rs st = foldl' (doRound m mix) st rs 100 | 101 | m1 b c d = d `xor` (b .&. (c `xor` d)) 102 | m2 b c d = c `xor` (d .&. (b `xor` c)) 103 | m3 b c d = b `xor` c `xor` d 104 | m4 b c d = c `xor` (b .|. complement d) 105 | 106 | rs1 = zipWith3 Round stable1 ktable1 gtable1 107 | rs2 = zipWith3 Round stable2 ktable2 gtable2 108 | rs3 = zipWith3 Round stable3 ktable3 gtable3 109 | rs4 = zipWith3 Round stable4 ktable4 gtable4 110 | 111 | data Round = Round !Int !Word32 !Int 112 | 113 | doRound :: 114 | Vector Word32 {- ^ message chunk -} -> 115 | Mixer {- ^ mixing function for this round -} -> 116 | Context {- ^ incoming state -} -> 117 | Round {- ^ rotation, magic, chunk index -} -> 118 | Context 119 | doRound m mixer (Context a b c d) (Round s k g) = Context d (b + z) b c 120 | where 121 | f = mixer b c d 122 | y = a + f + k + m Vector.! g 123 | z = rotateL y s 124 | 125 | type Mixer = Word32 -> Word32 -> Word32 -> Word32 126 | 127 | toFixedByteString :: Int -> Builder -> L.ByteString 128 | toFixedByteString n = toLazyByteStringWith (untrimmedStrategy n 0) L.empty 129 | 130 | ------------------------------------------------------------------------ 131 | -- Magic numbers 132 | ------------------------------------------------------------------------ 133 | 134 | stable1, stable2, stable3, stable4 :: [Int] 135 | stable1 = [ 7, 12, 17, 22, 7, 12, 17, 22, 7, 12, 17, 22, 7, 12, 17, 22] 136 | stable2 = [ 5, 9, 14, 20, 5, 9, 14, 20, 5, 9, 14, 20, 5, 9, 14, 20] 137 | stable3 = [ 4, 11, 16, 23, 4, 11, 16, 23, 4, 11, 16, 23, 4, 11, 16, 23] 138 | stable4 = [ 6, 10, 15, 21, 6, 10, 15, 21, 6, 10, 15, 21, 6, 10, 15, 21] 139 | 140 | 141 | ktable1, ktable2, ktable3, ktable4 :: [Word32] 142 | ktable1 = [ 0xd76aa478, 0xe8c7b756, 0x242070db, 0xc1bdceee 143 | , 0xf57c0faf, 0x4787c62a, 0xa8304613, 0xfd469501 144 | , 0x698098d8, 0x8b44f7af, 0xffff5bb1, 0x895cd7be 145 | , 0x6b901122, 0xfd987193, 0xa679438e, 0x49b40821] 146 | ktable2 = [ 0xf61e2562, 0xc040b340, 0x265e5a51, 0xe9b6c7aa 147 | , 0xd62f105d, 0x02441453, 0xd8a1e681, 0xe7d3fbc8 148 | , 0x21e1cde6, 0xc33707d6, 0xf4d50d87, 0x455a14ed 149 | , 0xa9e3e905, 0xfcefa3f8, 0x676f02d9, 0x8d2a4c8a] 150 | ktable3 = [ 0xfffa3942, 0x8771f681, 0x6d9d6122, 0xfde5380c 151 | , 0xa4beea44, 0x4bdecfa9, 0xf6bb4b60, 0xbebfbc70 152 | , 0x289b7ec6, 0xeaa127fa, 0xd4ef3085, 0x04881d05 153 | , 0xd9d4d039, 0xe6db99e5, 0x1fa27cf8, 0xc4ac5665] 154 | ktable4 = [ 0xf4292244, 0x432aff97, 0xab9423a7, 0xfc93a039 155 | , 0x655b59c3, 0x8f0ccc92, 0xffeff47d, 0x85845dd1 156 | , 0x6fa87e4f, 0xfe2ce6e0, 0xa3014314, 0x4e0811a1 157 | , 0xf7537e82, 0xbd3af235, 0x2ad7d2bb, 0xeb86d391 158 | ] 159 | 160 | gtable1, gtable2, gtable3, gtable4 :: [Int] 161 | gtable1 = [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15] 162 | gtable2 = [ 1, 6, 11, 0, 5, 10, 15, 4, 9, 14, 3, 8, 13, 2, 7, 12] 163 | gtable3 = [ 5, 8, 11, 14, 1, 4, 7, 10, 13, 0, 3, 6, 9, 12, 15, 2] 164 | gtable4 = [ 0, 7, 14, 5, 12, 3, 10, 1, 8, 15, 6, 13, 4, 11, 2, 9] 165 | 166 | initialState :: Context 167 | initialState = Context 0x67452301 0xefcdab89 0x98badcfe 0x10325476 168 | -------------------------------------------------------------------------------- /Day5.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Data.List 4 | 5 | main :: IO () 6 | main = 7 | do strs <- loadInput 8 | print (length (filter part1 strs)) 9 | print (length (filter part2 strs)) 10 | 11 | part1 :: String -> Bool 12 | part1 str = threeVowels str && hasDouble str && noProhibited str 13 | 14 | part2 :: String -> Bool 15 | part2 str = pairTwice str && nearby str 16 | 17 | threeVowels :: String -> Bool 18 | threeVowels = not . null . drop 2 . filter (`elem` "aeiou") 19 | 20 | hasDouble :: String -> Bool 21 | hasDouble = search $ \str -> 22 | case str of 23 | x:y:_ -> x == y 24 | _ -> False 25 | 26 | noProhibited :: String -> Bool 27 | noProhibited str = not (any (`isInfixOf` str) ["ab","cd","pq","xy"]) 28 | 29 | search :: (String -> Bool) -> String -> Bool 30 | search p = any p . tails 31 | 32 | pairTwice :: String -> Bool 33 | pairTwice = search $ \str -> 34 | case str of 35 | x:y:z -> [x,y] `isInfixOf` z 36 | _ -> False 37 | 38 | nearby :: String -> Bool 39 | nearby = search $ \str -> 40 | case str of 41 | w:_:y:_ -> w == y 42 | _ -> False 43 | 44 | loadInput :: IO [String] 45 | loadInput = lines <$> readFile "input5.txt" 46 | -------------------------------------------------------------------------------- /Day6.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Data.Array.ST 4 | import Data.Foldable 5 | import Control.Monad.ST 6 | 7 | data Op = On | Off | Toggle 8 | type Point = (Int,Int) 9 | data Command = Command !Op Point Point 10 | 11 | main :: IO () 12 | main = 13 | do cmds <- loadInput 14 | print (runST (part1 cmds)) 15 | print (runST (part2 cmds)) 16 | 17 | part1 :: [Command] -> ST s Int 18 | part1 cmds = 19 | do a <- newBitGrid 20 | traverse_ (bitCommand a) cmds 21 | xs <- getElems a 22 | return $! length (filter id xs) 23 | 24 | part2 :: [Command] -> ST s Int 25 | part2 cmds = 26 | do a <- newIntGrid 27 | traverse_ (intCommand a) cmds 28 | xs <- getElems a 29 | return $! sum xs 30 | 31 | bitCommand :: STUArray s Point Bool -> Command -> ST s () 32 | bitCommand a (Command op x y) = 33 | forRange x y $ \p -> 34 | case op of 35 | On -> writeArray a p True 36 | Off -> writeArray a p False 37 | Toggle -> writeArray a p . not =<< readArray a p 38 | 39 | intCommand :: STUArray s Point Int -> Command -> ST s () 40 | intCommand a (Command op x y) = 41 | forRange x y $ \p -> 42 | writeArray a p . upd =<< readArray a p 43 | where 44 | upd = case op of 45 | On -> (+1) 46 | Off -> max 0 . subtract 1 47 | Toggle -> (+2) 48 | 49 | forRange :: Applicative m => Point -> Point -> (Point -> m a) -> m () 50 | forRange (xlo,ylo) (xhi,yhi) k = 51 | for_ [xlo..xhi] $ \x -> 52 | for_ [ylo..yhi] $ \y -> 53 | k (x,y) 54 | {-# INLINE forRange #-} 55 | 56 | loadInput :: IO [Command] 57 | loadInput = map parseLine . lines <$> readFile "input6.txt" 58 | 59 | newBitGrid :: ST s (STUArray s Point Bool) 60 | newBitGrid = newArray ((0,0),(999,999)) False 61 | 62 | newIntGrid :: ST s (STUArray s Point Int) 63 | newIntGrid = newArray ((0,0),(999,999)) 0 64 | 65 | parseLine :: String -> Command 66 | parseLine str = Command op (parsePoint p1) (parsePoint p2) 67 | where 68 | (op,p1,p2) = 69 | case words str of 70 | ["turn","on", x,"through",y] -> (On, x, y) 71 | ["turn","off",x,"through",y] -> (Off, x, y) 72 | ["toggle", x,"through",y] -> (Toggle, x, y) 73 | _ -> error ("Bad line: " ++ str) 74 | 75 | parsePoint :: String -> Point 76 | parsePoint str = 77 | foldr const (error ("Bad point: " ++ str)) $ 78 | do (x,',':ystr) <- reads str 79 | (y,[] ) <- reads ystr 80 | return (x,y) 81 | -------------------------------------------------------------------------------- /Day7.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE DeriveFunctor #-} 2 | module Main where 3 | 4 | import Data.Bits 5 | import Data.Map (Map) 6 | import Data.Word 7 | import Text.Read (readMaybe) 8 | import qualified Data.Map as Map 9 | 10 | data Gate a = Gate1 Op1 a | Gate2 Op2 a a deriving Functor 11 | data Op1 = Not | Id 12 | data Op2 = And | Or | LShift | RShift 13 | 14 | main :: IO () 15 | main = 16 | do circuit1 <- loadInput 17 | let answer1 = findAnswer circuit1 18 | print answer1 19 | 20 | let circuit2 = Map.insert "b" (Gate1 Id (show answer1)) circuit1 21 | print (findAnswer circuit2) 22 | 23 | loadInput :: IO (Map String (Gate String)) 24 | loadInput = parseLines <$> readFile "input7.txt" 25 | 26 | -- | Build a circuit and compute output 'a' 27 | findAnswer :: Map String (Gate String) -> Word16 28 | findAnswer circuit = tieCircuit circuit Map.! "a" 29 | 30 | tieCircuit :: Map String (Gate String) -> Map String Word16 31 | tieCircuit m = m' 32 | where 33 | m' = fmap (evalGate . fmap evalKey) m 34 | 35 | evalKey key 36 | | Just n <- readMaybe key = n 37 | | otherwise = m' Map.! key 38 | 39 | evalGate :: Gate Word16 -> Word16 40 | evalGate (Gate1 Id x ) = x 41 | evalGate (Gate1 Not x ) = complement x 42 | evalGate (Gate2 And x y) = x .&. y 43 | evalGate (Gate2 Or x y) = x .|. y 44 | evalGate (Gate2 RShift x y) = x `shiftR` fromIntegral y 45 | evalGate (Gate2 LShift x y) = x `shiftL` fromIntegral y 46 | 47 | parseLines :: String -> Map String (Gate String) 48 | parseLines = Map.fromList . map parseLine . lines 49 | 50 | -- | Parse a line describing a gate in the circuit. 51 | parseLine :: String -> (String, Gate String) 52 | parseLine cmd = 53 | case words cmd of 54 | [x, "->",y] -> (y, Gate1 Id x) 55 | ["NOT",x, "->",y] -> (y, Gate1 Not x) 56 | [x,"AND", y,"->",z] -> (z, Gate2 And x y) 57 | [x,"OR", y,"->",z] -> (z, Gate2 Or x y) 58 | [x,"LSHIFT",y,"->",z] -> (z, Gate2 LShift x y) 59 | [x,"RSHIFT",y,"->",z] -> (z, Gate2 RShift x y) 60 | _ -> error ("parseLine: " ++ cmd) 61 | -------------------------------------------------------------------------------- /Day8.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | main :: IO () 4 | main = 5 | do ws <- loadInput 6 | print (sum (part1 <$> ws)) 7 | print (sum (part2 <$> ws)) 8 | 9 | loadInput :: IO [String] 10 | loadInput = lines <$> readFile "input8.txt" 11 | 12 | part1 :: String -> Int 13 | part1 str = 2 + sum (aux (init (tail str))) 14 | where 15 | aux ('\\':'"' :xs) = 1 : aux xs 16 | aux ('\\':'\\' :xs) = 1 : aux xs 17 | aux ('\\':'x':_:_:xs) = 3 : aux xs 18 | aux (_ :xs) = aux xs 19 | aux [] = [] 20 | 21 | part2 :: String -> Int 22 | part2 str = 2 + count isExpand str 23 | where 24 | isExpand x = x `elem` "\\\"" 25 | 26 | count :: (a -> Bool) -> [a] -> Int 27 | count p xs = length (filter p xs) 28 | -------------------------------------------------------------------------------- /Day9.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import qualified Data.Map as Map 4 | import qualified Data.Set as Set 5 | import Data.Map ( Map ) 6 | import Data.List 7 | 8 | data Edge = Edge String String deriving (Eq, Ord, Show, Read) 9 | 10 | edge :: String -> String -> Edge 11 | edge x y 12 | | x < y = Edge x y 13 | | otherwise = Edge y x 14 | 15 | edgeParts :: Edge -> [String] 16 | edgeParts (Edge x y) = [x,y] 17 | 18 | main :: IO () 19 | main = 20 | do input <- loadInput "input9.txt" 21 | let places = uniques (concatMap edgeParts (Map.keys input)) 22 | costs = tripLength input <$> permutations places 23 | print (minimum costs) 24 | print (maximum costs) 25 | 26 | loadInput :: FilePath -> IO (Map Edge Int) 27 | loadInput filename = Map.fromList . map parse . lines <$> readFile filename 28 | 29 | parse :: String -> (Edge, Int) 30 | parse ln = 31 | case words ln of 32 | [x,"to",y,"=",z] -> (edge x y,read z) 33 | _ -> error ("Bad line: " ++ ln) 34 | 35 | tripLength :: Map Edge Int -> [String] -> Int 36 | tripLength m xs = sum (zipWith edgeLength xs (tail xs)) 37 | where 38 | edgeLength x y = m Map.! edge x y 39 | 40 | uniques :: Ord a => [a] -> [a] 41 | uniques = Set.toList . Set.fromList 42 | -------------------------------------------------------------------------------- /LICENSE: -------------------------------------------------------------------------------- 1 | Copyright (c) 2015 Eric Mertens 2 | 3 | Permission to use, copy, modify, and/or distribute this software for any purpose 4 | with or without fee is hereby granted, provided that the above copyright notice 5 | and this permission notice appear in all copies. 6 | 7 | THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES WITH 8 | REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY AND 9 | FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY SPECIAL, DIRECT, 10 | INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER RESULTING FROM LOSS 11 | OF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF CONTRACT, NEGLIGENCE OR OTHER 12 | TORTIOUS ACTION, ARISING OUT OF OR IN CONNECTION WITH THE USE OR PERFORMANCE OF 13 | THIS SOFTWARE. 14 | -------------------------------------------------------------------------------- /Makefile: -------------------------------------------------------------------------------- 1 | .PHONY: clean 2 | 3 | clean: 4 | rm *.hi *.o 5 | -------------------------------------------------------------------------------- /Setup.hs: -------------------------------------------------------------------------------- 1 | import Distribution.Simple 2 | main = defaultMain 3 | -------------------------------------------------------------------------------- /advent.cabal: -------------------------------------------------------------------------------- 1 | cabal-version: 2.4 2 | name: advent 3 | version: 0 4 | synopsis: My solutions to the 2015 adventofcode.com 5 | description: My solutions to the 2015 adventofcode.com 6 | license: ISC 7 | license-file: LICENSE 8 | author: Eric Mertens 9 | maintainer: emertens@gmail.com 10 | copyright: 2015 Eric Mertens 11 | build-type: Simple 12 | tested-with: GHC==8.10.3 13 | 14 | source-repository head 15 | type: git 16 | location: https://github.com/glguy/advent2015 17 | 18 | executable Day1 19 | main-is: Day1.hs 20 | build-depends: base ^>= 4.14 21 | default-language: Haskell2010 22 | 23 | executable Day2 24 | main-is: Day2.hs 25 | build-depends: base ^>= 4.14, split >=0.2 && <0.3 26 | default-language: Haskell2010 27 | 28 | executable Day3 29 | main-is: Day3.hs 30 | build-depends: base ^>= 4.14, 31 | split >=0.2 && <0.3, 32 | containers >=0.5 && <0.7 33 | default-language: Haskell2010 34 | 35 | executable Day4 36 | main-is: Day4.hs 37 | build-depends: base ^>= 4.14, 38 | binary >=0.7.5 && <0.11, 39 | bytestring, 40 | vector >=0.11 && <0.13 41 | default-language: Haskell2010 42 | 43 | executable Day5 44 | main-is: Day5.hs 45 | build-depends: base ^>= 4.14, 46 | default-language: Haskell2010 47 | 48 | executable Day6 49 | main-is: Day6.hs 50 | build-depends: base ^>= 4.14, array >=0.5 && <0.6 51 | default-language: Haskell2010 52 | 53 | executable Day7 54 | main-is: Day7.hs 55 | build-depends: base ^>= 4.14, containers >=0.5 && <0.7 56 | default-language: Haskell2010 57 | 58 | executable Day8 59 | main-is: Day8.hs 60 | build-depends: base ^>= 4.14 61 | default-language: Haskell2010 62 | 63 | executable Day9 64 | main-is: Day9.hs 65 | build-depends: base ^>= 4.14, containers >=0.5 && <0.7 66 | default-language: Haskell2010 67 | 68 | executable Day10 69 | main-is: Day10.hs 70 | build-depends: base ^>= 4.14 71 | default-language: Haskell2010 72 | 73 | executable Day11 74 | main-is: Day11.hs 75 | build-depends: base ^>= 4.14 76 | default-language: Haskell2010 77 | 78 | executable Day12 79 | main-is: Day12.hs 80 | build-depends: base ^>= 4.14, 81 | bytestring, 82 | aeson ^>= 1.5.4, 83 | scientific >=0.3 && <0.4 84 | default-language: Haskell2010 85 | 86 | executable Day13 87 | main-is: Day13.hs 88 | build-depends: base ^>= 4.14, 89 | containers >=0.5 && <0.7 90 | default-language: Haskell2010 91 | 92 | executable Day14 93 | main-is: Day14.hs 94 | build-depends: base ^>= 4.14, 95 | default-language: Haskell2010 96 | 97 | executable Day15 98 | main-is: Day15.hs 99 | build-depends: base ^>= 4.14, 100 | default-language: Haskell2010 101 | 102 | executable Day16 103 | main-is: Day16.hs 104 | build-depends: base ^>= 4.14, 105 | default-language: Haskell2010 106 | 107 | executable Day17 108 | main-is: Day17.hs 109 | build-depends: base ^>= 4.14, array >=0.5 && <0.6 110 | default-language: Haskell2010 111 | 112 | executable Day18 113 | main-is: Day18.hs 114 | build-depends: base ^>= 4.14, array >=0.5 && <0.6 115 | default-language: Haskell2010 116 | 117 | executable Day19 118 | main-is: Day19.hs 119 | build-depends: base ^>= 4.14, 120 | array >=0.5 && <0.6, 121 | containers >=0.5 && <0.7 122 | default-language: Haskell2010 123 | 124 | executable Day20 125 | main-is: Day20.hs 126 | build-depends: base ^>= 4.14, 127 | array >=0.5 && <0.6, 128 | default-language: Haskell2010 129 | 130 | executable Day21 131 | main-is: Day21.hs 132 | build-depends: base ^>= 4.14, 133 | default-language: Haskell2010 134 | 135 | executable Day22 136 | main-is: Day22.hs 137 | build-depends: base ^>= 4.14, 138 | containers >=0.5 && <0.7 139 | default-language: Haskell2010 140 | 141 | executable Day23 142 | main-is: Day23.hs 143 | other-modules: Day23TH 144 | build-depends: base ^>= 4.14, array >=0.5 && <0.6, template-haskell 145 | default-language: Haskell2010 146 | 147 | executable Day24 148 | main-is: Day24.hs 149 | build-depends: base ^>= 4.14 150 | default-language: Haskell2010 151 | 152 | executable Day25 153 | main-is: Day25.hs 154 | build-depends: base ^>= 4.14, integer-gmp >=1.0 && <1.1 155 | default-language: Haskell2010 156 | -------------------------------------------------------------------------------- /asm/Day2.asm: -------------------------------------------------------------------------------- 1 | # load x y z into F G H 2 | top: CALL getnumber 3 | JF A end 4 | SET F A 5 | CALL getnumber 6 | SET G A 7 | CALL getnumber 8 | SET H A 9 | 10 | # surface area added to D 11 | MULT A F G 12 | MULT B G H 13 | ADD A A B 14 | MULT B F H 15 | ADD A A B 16 | MULT A A 2 17 | ADD D D A 18 | 19 | # volume added to E 20 | MULT A F G 21 | MULT A A H 22 | ADD E E A 23 | 24 | GT A F G 25 | JF A skip_swap_1 26 | SET A F 27 | SET F G 28 | SET G A 29 | 30 | skip_swap_1: GT A G H 31 | JF A skip_swap_2 32 | SET A G 33 | SET G H 34 | SET H A 35 | 36 | skip_swap_2: MULT A F G 37 | ADD D D A 38 | 39 | ADD A F G 40 | ADD E E A 41 | ADD E E A 42 | 43 | JMP top 44 | 45 | end: SET A D 46 | CALL printnumber 47 | OUT '\n' 48 | SET A E 49 | CALL printnumber 50 | OUT '\n' 51 | HALT 52 | 53 | getnumber: PUSH B 54 | PUSH C 55 | 56 | SET A 0 57 | getnumber_loop: IN B 58 | 59 | #too small 60 | GT C '0' B 61 | JT C getnumber_done 62 | 63 | ADD B B -48 # -'0' 64 | 65 | #too big 66 | GT C 10 B 67 | JF C getnumber_done 68 | 69 | MULT A A 10 70 | ADD A A B 71 | JMP getnumber_loop 72 | 73 | getnumber_done: POP C 74 | POP B 75 | RET 76 | 77 | ### printnumber ######################################## 78 | # Print a number in signed, decimal notation 79 | # 80 | # Arguments: A, number to print 81 | # Results: None 82 | printnumber: PUSH A # Number to print 83 | PUSH B # Temporary condition 84 | PUSH C # Output character 85 | 86 | GT B A 0x3fff # test for negative 87 | JF B printnumber_positive 88 | 89 | OUT '-' 90 | MULT A A -1 91 | 92 | 93 | printnumber_positive: GT B 10 A 94 | JT B printnumber_1 95 | GT B 100 A 96 | JT B printnumber_10 97 | GT B 1000 A 98 | JT B printnumber_100 99 | GT B 10000 A 100 | JT B printnumber_1000 101 | 102 | printnumber_10000: SET C '0' 103 | printnumber_10000_loop: GT B 10000 A 104 | JT B printnumber_10000_done 105 | ADD A A -10000 106 | ADD C C 1 107 | JMP printnumber_10000_loop 108 | printnumber_10000_done: OUT C 109 | 110 | printnumber_1000: SET C '0' 111 | printnumber_1000_loop: GT B 1000 A 112 | JT B printnumber_1000_done 113 | ADD A A -1000 114 | ADD C C 1 115 | JMP printnumber_1000_loop 116 | printnumber_1000_done: OUT C 117 | 118 | printnumber_100: SET C '0' 119 | printnumber_100_loop: GT B 100 A 120 | JT B printnumber_100_done 121 | ADD A A -100 122 | ADD C C 1 123 | JMP printnumber_100_loop 124 | printnumber_100_done: OUT C 125 | 126 | printnumber_10: SET C '0' 127 | printnumber_10_loop: GT B 10 A 128 | JT B printnumber_10_done 129 | ADD A A -10 130 | ADD C C 1 131 | JMP printnumber_10_loop 132 | printnumber_10_done: OUT C 133 | 134 | printnumber_1: ADD C A '0' 135 | OUT C 136 | 137 | POP C 138 | POP B 139 | POP A 140 | RET 141 | ### END OF printnumber ################################# 142 | -------------------------------------------------------------------------------- /asm/input2.txt: -------------------------------------------------------------------------------- 1 | 20x3x11 2 | 15x27x5 3 | 6x29x7 4 | 30x15x9 5 | 19x29x21 6 | 10x4x15 7 | 1x26x4 8 | 1x5x18 9 | 10x15x23 10 | 10x14x20 11 | 3x5x18 12 | 29x23x30 13 | 7x4x10 14 | 22x24x29 15 | 30x1x2 16 | 19x2x5 17 | 11x9x22 18 | 23x15x10 19 | 11x11x10 20 | 30x28x5 21 | 22x5x4 22 | 6x26x20 23 | 16x12x30 24 | 10x20x5 25 | 25x14x24 26 | 16x17x22 27 | 11x28x26 28 | 1x11x10 29 | 1x24x15 30 | 13x17x21 31 | 30x3x13 32 | 20x25x17 33 | 22x12x5 34 | 22x20x24 35 | 9x2x14 36 | 6x18x8 37 | 27x28x24 38 | 11x17x1 39 | 1x4x12 40 | 5x20x13 41 | 24x23x23 42 | 22x1x25 43 | 18x19x5 44 | 5x23x13 45 | 8x16x4 46 | 20x21x9 47 | 1x7x11 48 | 8x30x17 49 | 3x30x9 50 | 6x16x18 51 | 22x25x27 52 | 9x20x26 53 | 16x21x23 54 | 5x24x17 55 | 15x17x15 56 | 26x15x10 57 | 22x16x3 58 | 20x24x24 59 | 8x18x10 60 | 23x19x16 61 | 1x21x24 62 | 23x23x9 63 | 14x20x6 64 | 25x5x5 65 | 16x3x1 66 | 29x29x20 67 | 11x4x26 68 | 10x23x24 69 | 29x25x16 70 | 27x27x22 71 | 9x7x22 72 | 6x21x18 73 | 25x11x19 74 | 14x13x3 75 | 15x28x17 76 | 14x3x12 77 | 29x8x19 78 | 30x14x20 79 | 20x23x4 80 | 8x16x5 81 | 4x11x18 82 | 20x8x24 83 | 21x13x21 84 | 14x26x29 85 | 27x4x17 86 | 27x4x25 87 | 5x28x6 88 | 23x24x11 89 | 29x22x5 90 | 30x20x6 91 | 23x2x10 92 | 11x4x7 93 | 27x23x6 94 | 10x20x19 95 | 8x20x22 96 | 5x29x22 97 | 16x13x2 98 | 2x11x14 99 | 6x12x4 100 | 3x13x6 101 | 16x5x18 102 | 25x3x28 103 | 21x1x5 104 | 20x16x19 105 | 28x30x27 106 | 26x7x18 107 | 25x27x24 108 | 11x19x7 109 | 21x19x17 110 | 2x12x27 111 | 20x5x14 112 | 8x5x8 113 | 6x24x8 114 | 7x28x20 115 | 3x20x28 116 | 5x20x30 117 | 13x29x1 118 | 26x29x5 119 | 19x28x25 120 | 5x19x11 121 | 11x20x22 122 | 4x23x1 123 | 19x25x12 124 | 3x10x6 125 | 3x14x10 126 | 28x16x12 127 | 23x12x2 128 | 23x12x19 129 | 20x28x10 130 | 9x10x25 131 | 16x21x16 132 | 1x18x20 133 | 9x4x26 134 | 3x25x8 135 | 17x16x28 136 | 9x28x16 137 | 27x3x12 138 | 17x24x12 139 | 13x21x10 140 | 7x17x13 141 | 6x10x9 142 | 7x29x25 143 | 11x19x30 144 | 1x24x5 145 | 20x16x23 146 | 24x28x21 147 | 6x29x19 148 | 25x2x19 149 | 12x5x26 150 | 25x29x12 151 | 16x28x22 152 | 26x26x15 153 | 9x13x5 154 | 10x29x7 155 | 1x24x16 156 | 22x2x2 157 | 6x16x13 158 | 3x12x28 159 | 4x12x13 160 | 14x27x21 161 | 14x23x26 162 | 7x5x18 163 | 8x30x27 164 | 15x9x18 165 | 26x16x5 166 | 3x29x17 167 | 19x7x18 168 | 16x18x1 169 | 26x15x30 170 | 24x30x21 171 | 13x20x7 172 | 4x12x10 173 | 27x20x11 174 | 28x29x21 175 | 20x14x30 176 | 28x12x3 177 | 19x1x8 178 | 4x8x6 179 | 21x14x2 180 | 27x19x21 181 | 17x24x14 182 | 15x18x11 183 | 18x7x26 184 | 25x28x29 185 | 27x26x9 186 | 18x12x17 187 | 24x28x25 188 | 13x24x14 189 | 26x9x28 190 | 9x3x30 191 | 9x2x9 192 | 8x1x29 193 | 18x30x10 194 | 18x14x5 195 | 26x8x30 196 | 12x1x1 197 | 30x5x28 198 | 26x17x21 199 | 10x10x10 200 | 20x7x27 201 | 13x17x6 202 | 21x13x17 203 | 2x16x8 204 | 7x9x9 205 | 15x26x4 206 | 11x28x25 207 | 10x6x19 208 | 21x6x29 209 | 15x5x6 210 | 28x9x16 211 | 14x3x10 212 | 12x29x5 213 | 22x19x19 214 | 25x15x22 215 | 30x6x28 216 | 11x23x13 217 | 20x25x14 218 | 26x1x13 219 | 6x14x15 220 | 16x25x17 221 | 28x4x13 222 | 10x24x25 223 | 4x13x10 224 | 9x15x16 225 | 15x24x6 226 | 22x9x19 227 | 11x11x8 228 | 4x19x12 229 | 24x5x4 230 | 27x12x13 231 | 7x27x16 232 | 2x6x9 233 | 29x27x15 234 | 18x26x23 235 | 19x16x15 236 | 14x5x25 237 | 9x16x30 238 | 4x6x4 239 | 13x10x10 240 | 1x8x29 241 | 23x5x17 242 | 19x20x20 243 | 11x27x24 244 | 27x15x5 245 | 15x11x12 246 | 21x11x3 247 | 1x13x22 248 | 17x8x8 249 | 13x14x14 250 | 17x22x7 251 | 9x5x8 252 | 2x6x3 253 | 25x9x15 254 | 11x8x13 255 | 9x25x12 256 | 3x16x12 257 | 12x16x8 258 | 16x24x17 259 | 4x6x26 260 | 22x29x11 261 | 14x17x19 262 | 28x2x27 263 | 24x22x19 264 | 22x20x30 265 | 23x28x4 266 | 16x12x14 267 | 22x24x22 268 | 29x1x28 269 | 26x29x16 270 | 3x25x30 271 | 27x3x13 272 | 22x24x26 273 | 25x3x2 274 | 7x24x2 275 | 10x5x3 276 | 28x8x29 277 | 25x6x4 278 | 12x17x14 279 | 24x3x5 280 | 23x27x7 281 | 26x23x30 282 | 11x10x19 283 | 23x7x11 284 | 26x14x15 285 | 14x3x25 286 | 12x24x14 287 | 2x14x12 288 | 9x12x16 289 | 9x2x28 290 | 3x8x2 291 | 22x6x9 292 | 2x30x2 293 | 25x1x9 294 | 20x11x2 295 | 14x11x12 296 | 7x14x12 297 | 24x8x26 298 | 13x21x23 299 | 18x17x23 300 | 13x6x17 301 | 20x20x19 302 | 13x17x29 303 | 7x24x24 304 | 23x8x6 305 | 19x10x28 306 | 3x8x21 307 | 15x20x18 308 | 11x27x1 309 | 11x24x28 310 | 13x20x11 311 | 18x19x22 312 | 27x22x12 313 | 28x3x2 314 | 13x4x29 315 | 26x5x6 316 | 14x29x25 317 | 7x4x7 318 | 5x17x7 319 | 2x8x1 320 | 22x30x24 321 | 22x21x28 322 | 1x28x13 323 | 11x20x4 324 | 25x29x19 325 | 9x23x4 326 | 30x6x11 327 | 25x18x10 328 | 28x10x24 329 | 3x5x20 330 | 19x28x10 331 | 27x19x2 332 | 26x20x4 333 | 19x21x6 334 | 2x12x30 335 | 8x26x27 336 | 11x27x10 337 | 14x13x17 338 | 4x3x21 339 | 2x20x21 340 | 22x30x3 341 | 2x23x2 342 | 3x16x12 343 | 22x28x22 344 | 3x23x29 345 | 8x25x15 346 | 9x30x4 347 | 10x11x1 348 | 24x8x20 349 | 10x7x27 350 | 7x22x4 351 | 27x13x17 352 | 5x28x5 353 | 30x15x13 354 | 10x8x17 355 | 8x21x5 356 | 8x17x26 357 | 25x16x4 358 | 9x7x25 359 | 13x11x20 360 | 6x30x9 361 | 15x14x12 362 | 30x1x23 363 | 5x20x24 364 | 22x7x6 365 | 26x11x23 366 | 29x7x5 367 | 13x24x28 368 | 22x20x10 369 | 18x3x1 370 | 15x19x23 371 | 28x28x20 372 | 7x26x2 373 | 9x12x20 374 | 15x4x6 375 | 1x17x21 376 | 3x22x17 377 | 9x4x20 378 | 25x19x5 379 | 9x11x22 380 | 14x1x17 381 | 14x5x16 382 | 30x5x18 383 | 19x6x12 384 | 28x16x22 385 | 13x4x25 386 | 29x23x18 387 | 1x27x3 388 | 12x14x4 389 | 10x25x19 390 | 15x19x30 391 | 11x30x4 392 | 11x22x26 393 | 13x25x2 394 | 17x13x27 395 | 11x30x24 396 | 15x1x14 397 | 17x18x4 398 | 26x11x3 399 | 16x22x28 400 | 13x20x9 401 | 1x18x3 402 | 25x11x12 403 | 20x21x1 404 | 22x27x4 405 | 8x28x23 406 | 7x13x27 407 | 17x9x26 408 | 27x27x20 409 | 11x20x12 410 | 26x21x11 411 | 29x14x12 412 | 27x25x1 413 | 28x29x25 414 | 21x23x28 415 | 5x18x18 416 | 19x5x4 417 | 7x6x30 418 | 27x8x11 419 | 12x24x12 420 | 16x25x22 421 | 26x11x29 422 | 25x22x17 423 | 15x23x23 424 | 17x9x6 425 | 30x10x16 426 | 21x3x5 427 | 18x27x2 428 | 28x21x14 429 | 16x18x17 430 | 4x18x2 431 | 9x1x14 432 | 9x1x9 433 | 5x27x12 434 | 8x16x30 435 | 3x19x19 436 | 16x26x24 437 | 1x6x9 438 | 15x14x3 439 | 11x7x19 440 | 8x19x3 441 | 17x26x26 442 | 6x18x11 443 | 19x12x4 444 | 29x20x16 445 | 20x17x23 446 | 6x6x5 447 | 20x30x19 448 | 18x25x18 449 | 2x26x2 450 | 3x1x1 451 | 14x25x18 452 | 3x1x6 453 | 11x14x18 454 | 17x23x27 455 | 25x29x9 456 | 6x25x20 457 | 20x10x9 458 | 17x5x18 459 | 29x14x8 460 | 14x25x26 461 | 10x15x29 462 | 23x19x11 463 | 22x2x2 464 | 4x5x5 465 | 13x23x25 466 | 19x13x19 467 | 20x18x6 468 | 30x7x28 469 | 26x18x17 470 | 29x18x10 471 | 30x29x1 472 | 12x26x24 473 | 18x17x26 474 | 29x28x15 475 | 3x12x20 476 | 24x10x8 477 | 30x15x6 478 | 28x23x15 479 | 14x28x11 480 | 10x27x19 481 | 14x8x21 482 | 24x1x23 483 | 1x3x27 484 | 6x15x6 485 | 8x25x26 486 | 13x10x25 487 | 6x9x8 488 | 10x29x29 489 | 26x23x5 490 | 14x24x1 491 | 25x6x22 492 | 17x11x18 493 | 1x27x26 494 | 18x25x23 495 | 20x15x6 496 | 2x21x28 497 | 2x10x13 498 | 12x25x14 499 | 2x14x23 500 | 30x5x23 501 | 29x19x21 502 | 29x10x25 503 | 14x22x16 504 | 17x11x26 505 | 12x17x30 506 | 8x17x7 507 | 20x25x28 508 | 20x11x30 509 | 15x1x12 510 | 13x3x24 511 | 16x23x23 512 | 27x3x3 513 | 26x3x27 514 | 18x5x12 515 | 12x26x7 516 | 19x27x12 517 | 20x10x28 518 | 30x12x25 519 | 3x14x10 520 | 21x26x1 521 | 24x26x26 522 | 7x21x30 523 | 3x29x12 524 | 29x28x5 525 | 5x20x7 526 | 27x11x2 527 | 15x20x4 528 | 16x15x15 529 | 19x13x7 530 | 7x17x15 531 | 27x24x15 532 | 9x17x28 533 | 20x21x14 534 | 14x29x29 535 | 23x26x13 536 | 27x23x21 537 | 18x13x6 538 | 26x16x21 539 | 18x26x27 540 | 9x3x12 541 | 30x18x24 542 | 12x11x29 543 | 5x15x1 544 | 1x16x3 545 | 14x28x11 546 | 2x18x1 547 | 19x18x19 548 | 18x28x21 549 | 2x3x14 550 | 22x16x5 551 | 28x18x28 552 | 24x16x18 553 | 7x4x10 554 | 19x26x19 555 | 24x17x7 556 | 25x9x6 557 | 25x17x7 558 | 20x22x20 559 | 3x3x7 560 | 23x19x15 561 | 21x27x21 562 | 1x23x11 563 | 9x19x4 564 | 22x4x18 565 | 6x15x5 566 | 15x25x2 567 | 23x11x20 568 | 27x16x6 569 | 27x8x5 570 | 10x10x19 571 | 22x14x1 572 | 7x1x29 573 | 8x11x17 574 | 27x9x27 575 | 28x9x24 576 | 17x7x3 577 | 26x23x8 578 | 7x6x30 579 | 25x28x2 580 | 1x30x25 581 | 3x18x18 582 | 28x27x15 583 | 14x14x1 584 | 10x25x29 585 | 18x12x9 586 | 20x28x16 587 | 26x27x22 588 | 8x26x1 589 | 21x2x12 590 | 25x16x14 591 | 21x19x5 592 | 12x9x22 593 | 16x5x4 594 | 5x4x16 595 | 25x29x3 596 | 4x29x13 597 | 15x16x29 598 | 8x11x24 599 | 30x11x20 600 | 17x21x14 601 | 12x24x10 602 | 10x12x6 603 | 3x26x30 604 | 15x14x25 605 | 20x12x21 606 | 13x11x16 607 | 15x13x3 608 | 5x17x29 609 | 6x3x23 610 | 9x26x11 611 | 30x1x8 612 | 14x10x30 613 | 18x30x10 614 | 13x19x19 615 | 16x19x17 616 | 28x7x10 617 | 28x29x4 618 | 3x21x10 619 | 4x28x24 620 | 7x28x9 621 | 2x4x9 622 | 25x27x13 623 | 6x12x15 624 | 4x18x20 625 | 20x1x16 626 | 5x13x24 627 | 11x11x10 628 | 12x9x23 629 | 1x9x30 630 | 17x28x24 631 | 9x5x27 632 | 21x15x16 633 | 17x4x14 634 | 8x14x4 635 | 13x10x7 636 | 17x12x14 637 | 9x19x19 638 | 2x7x21 639 | 8x24x23 640 | 19x5x12 641 | 11x23x21 642 | 13x3x1 643 | 5x27x15 644 | 12x25x25 645 | 13x21x16 646 | 9x17x11 647 | 1x15x21 648 | 4x26x17 649 | 11x5x15 650 | 23x10x15 651 | 12x17x21 652 | 27x15x1 653 | 4x29x14 654 | 5x24x25 655 | 10x10x12 656 | 18x12x9 657 | 11x24x23 658 | 24x23x3 659 | 28x12x15 660 | 29x9x14 661 | 11x25x8 662 | 5x12x2 663 | 26x26x29 664 | 9x21x2 665 | 8x8x25 666 | 1x16x30 667 | 17x29x20 668 | 9x22x13 669 | 7x18x16 670 | 3x3x23 671 | 26x25x30 672 | 15x23x24 673 | 20x23x5 674 | 20x16x10 675 | 23x7x8 676 | 20x18x26 677 | 8x27x6 678 | 30x23x23 679 | 7x7x24 680 | 21x11x15 681 | 1x30x25 682 | 26x27x22 683 | 30x28x13 684 | 20x13x13 685 | 3x1x15 686 | 16x7x1 687 | 7x25x15 688 | 12x7x18 689 | 16x9x23 690 | 16x12x18 691 | 29x5x2 692 | 17x7x7 693 | 21x17x5 694 | 9x9x17 695 | 26x16x10 696 | 29x29x23 697 | 17x26x10 698 | 5x19x17 699 | 1x10x1 700 | 14x21x20 701 | 13x6x4 702 | 13x13x3 703 | 23x4x18 704 | 4x16x3 705 | 16x30x11 706 | 2x11x2 707 | 15x30x15 708 | 20x30x22 709 | 18x12x16 710 | 23x5x16 711 | 6x14x15 712 | 9x4x11 713 | 30x23x21 714 | 20x7x12 715 | 7x18x6 716 | 15x6x5 717 | 18x22x19 718 | 16x10x22 719 | 26x20x25 720 | 9x25x25 721 | 29x21x10 722 | 9x21x24 723 | 7x18x21 724 | 14x3x15 725 | 18x19x19 726 | 4x29x17 727 | 14x10x9 728 | 2x26x14 729 | 13x3x24 730 | 4x4x17 731 | 6x27x24 732 | 2x18x3 733 | 14x25x2 734 | 30x14x17 735 | 11x6x14 736 | 4x10x18 737 | 15x4x2 738 | 27x7x10 739 | 13x24x1 740 | 7x12x6 741 | 25x22x26 742 | 19x2x18 743 | 23x29x2 744 | 2x15x4 745 | 12x6x9 746 | 16x14x29 747 | 9x17x3 748 | 21x9x12 749 | 23x18x22 750 | 10x8x4 751 | 29x2x7 752 | 19x27x15 753 | 4x24x27 754 | 25x20x14 755 | 8x23x19 756 | 1x24x19 757 | 6x20x10 758 | 15x8x5 759 | 18x28x5 760 | 17x23x22 761 | 9x16x13 762 | 30x24x4 763 | 26x3x13 764 | 12x22x18 765 | 29x17x29 766 | 26x4x16 767 | 15x7x20 768 | 9x15x30 769 | 12x7x18 770 | 28x19x18 771 | 11x23x23 772 | 24x20x1 773 | 20x3x24 774 | 1x26x1 775 | 14x10x6 776 | 5x27x24 777 | 13x21x12 778 | 20x20x5 779 | 6x28x9 780 | 11x26x11 781 | 26x29x12 782 | 21x4x11 783 | 20x11x17 784 | 22x27x20 785 | 19x11x21 786 | 2x11x11 787 | 13x5x7 788 | 12x10x25 789 | 21x28x1 790 | 15x30x17 791 | 28x19x1 792 | 4x19x12 793 | 11x4x12 794 | 4x10x30 795 | 11x18x5 796 | 22x20x12 797 | 3x7x27 798 | 20x26x4 799 | 13x27x26 800 | 23x14x13 801 | 4x19x7 802 | 26x27x16 803 | 20x5x20 804 | 18x5x8 805 | 19x21x1 806 | 22x8x1 807 | 29x4x1 808 | 24x10x15 809 | 24x9x20 810 | 10x3x8 811 | 29x30x3 812 | 2x8x24 813 | 16x7x18 814 | 2x11x23 815 | 23x15x16 816 | 21x12x6 817 | 24x28x9 818 | 6x1x13 819 | 14x29x20 820 | 27x24x13 821 | 16x26x8 822 | 5x6x17 823 | 21x8x1 824 | 28x19x21 825 | 1x14x16 826 | 18x2x9 827 | 29x28x10 828 | 22x26x27 829 | 18x26x23 830 | 22x24x2 831 | 28x26x1 832 | 27x29x12 833 | 30x13x11 834 | 1x25x5 835 | 13x30x18 836 | 3x13x22 837 | 22x10x11 838 | 2x7x7 839 | 18x17x8 840 | 9x22x26 841 | 30x18x16 842 | 10x2x3 843 | 7x27x13 844 | 3x20x16 845 | 9x21x16 846 | 1x18x15 847 | 21x30x30 848 | 4x25x23 849 | 3x11x7 850 | 5x6x12 851 | 27x1x20 852 | 13x15x24 853 | 23x29x2 854 | 13x5x24 855 | 22x16x15 856 | 28x14x3 857 | 29x24x9 858 | 2x20x4 859 | 30x10x4 860 | 23x7x20 861 | 22x12x21 862 | 3x19x11 863 | 4x28x28 864 | 5x4x7 865 | 28x12x25 866 | 2x16x26 867 | 23x20x7 868 | 5x21x29 869 | 9x21x16 870 | 9x6x10 871 | 9x6x4 872 | 24x14x29 873 | 28x11x6 874 | 10x22x1 875 | 21x30x20 876 | 13x17x8 877 | 2x25x24 878 | 19x21x3 879 | 28x8x14 880 | 6x29x28 881 | 27x10x28 882 | 30x11x12 883 | 17x2x10 884 | 14x19x17 885 | 2x11x4 886 | 26x1x2 887 | 13x4x4 888 | 23x20x18 889 | 2x17x21 890 | 28x7x15 891 | 3x3x27 892 | 24x17x30 893 | 28x28x20 894 | 21x5x29 895 | 13x12x19 896 | 24x29x29 897 | 19x10x6 898 | 19x12x14 899 | 21x4x17 900 | 27x16x1 901 | 4x17x30 902 | 23x23x18 903 | 23x15x27 904 | 26x2x11 905 | 12x8x8 906 | 15x23x26 907 | 30x17x15 908 | 17x17x15 909 | 24x4x30 910 | 9x9x10 911 | 14x25x20 912 | 25x11x19 913 | 20x7x1 914 | 9x21x3 915 | 7x19x9 916 | 10x6x19 917 | 26x12x30 918 | 21x9x20 919 | 15x11x6 920 | 30x21x9 921 | 10x18x17 922 | 22x9x8 923 | 8x30x26 924 | 28x12x27 925 | 17x17x7 926 | 11x13x8 927 | 5x3x21 928 | 24x1x29 929 | 1x28x2 930 | 18x28x10 931 | 8x29x14 932 | 26x26x27 933 | 17x10x25 934 | 22x30x3 935 | 27x9x13 936 | 21x21x4 937 | 30x29x16 938 | 22x7x20 939 | 24x10x2 940 | 16x29x17 941 | 28x15x17 942 | 19x19x22 943 | 9x8x6 944 | 26x23x24 945 | 25x4x27 946 | 16x12x2 947 | 11x6x18 948 | 19x14x8 949 | 9x29x13 950 | 23x30x19 951 | 10x16x1 952 | 4x21x28 953 | 23x25x25 954 | 19x9x16 955 | 30x11x12 956 | 24x3x9 957 | 28x19x4 958 | 18x12x9 959 | 7x1x25 960 | 28x7x1 961 | 24x3x12 962 | 30x24x22 963 | 27x24x26 964 | 9x30x30 965 | 29x10x8 966 | 4x6x18 967 | 10x1x15 968 | 10x4x26 969 | 23x20x16 970 | 6x3x14 971 | 30x8x16 972 | 25x14x20 973 | 11x9x3 974 | 15x23x25 975 | 8x30x22 976 | 22x19x18 977 | 25x1x12 978 | 27x25x7 979 | 25x23x3 980 | 13x20x8 981 | 5x30x7 982 | 18x19x27 983 | 20x23x3 984 | 1x17x21 985 | 21x21x27 986 | 13x1x24 987 | 7x30x20 988 | 21x9x18 989 | 23x26x6 990 | 22x9x29 991 | 17x6x21 992 | 28x28x29 993 | 19x25x26 994 | 9x27x21 995 | 5x26x8 996 | 11x19x1 997 | 10x1x18 998 | 29x4x8 999 | 21x2x22 1000 | 14x12x8 1001 | 0 1002 | -------------------------------------------------------------------------------- /input1.txt: -------------------------------------------------------------------------------- 1 | ()(((()))(()()()((((()(((())(()(()((((((()(()(((())))((()(((()))((())(()((()()()()(((())(((((((())))()()(()(()(())(((((()()()((())(((((()()))))()(())(((())(())((((((())())))(()())))()))))()())()())((()()((()()()()(()((((((((()()())((()()(((((()(((())((())(()))()((((()((((((((())()((()())(())((()))())((((()())(((((((((((()()(((((()(()))())(((()(()))())((()(()())())())(()(((())(())())()()(()(()((()))((()))))((((()(((()))))((((()(()(()())())()(((()((((())((((()(((()()(())()()()())((()((((((()((()()))()((()))()(()()((())))(((()(((()))((()((()(()))(((()()(()(()()()))))()()(((()(((())())))))((()(((())()(()(())((()())))((((())))(()(()(()())()((()())))(((()((()(())()()((()((())(()()((())(())()))()))((()(())()))())(((((((()(()()(()(())())))))))(()((((((())((((())((())())(()()))))()(())(()())()())((())(()))))(()))(()((()))()(()((((((()()()()((((((((()(()(())((()()(()()))(())()())()((())))()))()())(((()))(())()(())()))()((()((()(()()())(())()()()((())())))((()()(()()((()(())()()())(((()(()()))))(())))(()(()())()))()()))))))()))))((((((())))())))(()(())())(()())))))(()))()))))))()((()))))()))))(()(()((()())())(()()))))(((())()))())())())(((()(()()))(())()(())(())((((((()()))))((()(()))))))(()))())(((()()(()))()())()()()())))))))))))))(())(()))(()))((()(())(()())(())())(()())(())()()(()())))()()()))(())())()))())())(())((())))))))(())))(())))))()))))((())(()(((()))))(()))()((()(())))(()())(((((()))()())()()))))()))))()))())(()(()()()))()))))))((()))))))))))()((()))((()(())((())()()(()()))()(()))))()()(()))()))(((())))(())()((())(())(()())()())())))))))())))()((())))()))(()))()()))(((((((()))())(()()))(()()(()))()(()((()())()))))))(((()()()())))(())()))()())(()()))()()))))))))(())))()))()()))))))()))()())))()(())(())))))()(())()()(()()))))())((()))))()))))(()(((((()))))))))())))())()(())()()))))(())))())()()())()()())()(()))))()))()))))))))())))((()))()))()))())))()())()()())))())))(()((())()((()))())))))())()(())((())))))))))))())()())(())())())(()))(()))()))())(()(())())()())()()(()))))(()(())))))))(())))())(())))))))())()()(())())())))(())))))()))()(()())()(()))())())))))()()(()))()))))())))))))))()))))()))))))())()())()()))))()())))())))))))))))()()))))()()(((()))()()(())()))))((()))))(()))(())())))(())()))))))(()))()))))(())())))))()))(()())))))))))))))())))))))))()((()())(()())))))))((()))))(())(())))()(()())())))())())(()()()())))()))))))())))))())()()())))))))))))()()(()))))()())()))((()())(()))))()(()))))))))))()())())(((())(()))))())()))()))()))))))()))))))(()))))()))))()(())))(())))(()))())()()(()()))()))(()()))))))))()))(()))())(()()(()(()())()()))()))))))))(())))))((()()(()))())())))))()))())(()())()()))())))()(()()()()))((())())))())()(()()))()))))))))(()))(())))()))))(()(()())(()))))()())())()))()()))())))))))))))())()))))))()))))))))())))))()))))())(()())))(())()))())())))))()()(()()())(()())))()()))(((()))(()()()))))()))))()))))((())))()((((((()()))))))())))))))))))(((()))))))))))))(())())))))())(()))))))(()))((()))())))()(()((()))()))()))))))))))())()))()(()()))))())))())(())()(()))()))())(()))()))))(()()))()()(())))))()))(())(()(()()))(()()())))))(((()))))))()))))))))))))(())(()))))()())())()()((()()))())))))(()))))())))))))()()()))))))))())))()(((()()))(())))))(((())())))))((()))()(()))(()))))(()())))(()))())))))()))))(())(())))()((()))(())())))()()))()))))))))()))(()()()(()()()(()))())(())()())(((()))(())))))))))(((()())))()()))))))))()(())(()))()((((())(())(()())))()))(((())()()()))((()))(()))())())))())))(()))())()())())(()(())())()()()(())))())(())))(())))(())()))()))(()((()))))))))())(()))))))())(()()))()()))()(()(()())))()()(()((()((((((()))(())))()()()))())()))((()()(()))())((()(()(()))(()()))))()())))()))()())))))))()()((()())(())))()))(()))(())(()))())(()(())))()()))))))(((()(((()()))()(()(())())((()()))()))()))()))()(()()()(()))((()())()(())))()()))(((())()()())(())()((()()()()(()(())(()()))()(((((()())))((())))))(()()()))))(((()(())))()))((()((()(())()(()((())))((()())()(()))(((()())()()(()))(())(((()((()())()((())()())(((()()))((()((())(()))(()())(()()()))((()))(())(()((()()())((()))(())))(())(())(())))(()())))(((((()(()(((((()())((((()(()())(())(()()(((())((()(((()()(((()()((((((())))())(()((((((()(()))()))()()((()((()))))()(()()(()((()()))))))(((((()(((((())()()()(())())))))))()))((()()(())))(())(()()()())))))(()((((())))))))()()(((()(()(()(()(()())()()()(((((((((()()())()(()))((()()()()()(((((((()())()((())()))((((((()(()(()(()())(((()(((((((()(((())(((((((((())(())())()))((()(()))(((()()())(())(()(()()(((()(())()))())))(())((((((())(()()())()()(((()(((())(()(((())(((((((()(((((((((()))(())(()(()(()))))((()))()(())())())((()(()((()()))((()()((()(())(())(()((())(((())(((()()()((((((()()(())((((())()))))(())((()(()((())))(((((()(()()())())((())())))((())((()((()()((((((())(((()()(()())())(()(()))(()(()))())())()(((((((()(((()(())()()((())((()(()()((()(()()(((((((((((())((())((((((())((()((((()(()((((()(((((((())()((()))))())()((()((((()(()(((()((()())))(())())(((()(((())((((((()(((((((((()()(())))(()(((((()((((()())))((()((()((()(()()(((())((((((((((((()(((())(()(((((()))(()()(()()()()()()((())(((((((())(((((())))))())()(()()(()(()(((()()(((((())(()((()((()(((()()((()((((())()))()((((())(())))()())(((())(())(()()((()(((()()((((((((((()()(()())())(((((((((())((((()))()()((((())(()((((()(((())())(((((((((((()((((())))(())(()(((()(((()((())(((((()((()()(()(()()((((((()((((()((()(()((()(()((((((()))))()()(((((()((()(()(())()))(())(((((((()((((()())(()((()((()(()))())))(())((()))))(((((((()()()())(()))(()()((()())()((()((()()()(()(()()))(()())(())(((((()(((((((((((()((()(((()(((((((()()((((((()(((((()(()((()(((((())((((((()))((((())((()()((())(((())()(((((()()(((((()((()(()(((((((()(((((()((()((()((())(())((())(()))()()))(()()(()(()()(((((((()(((()(((())()(((((()((((((()())((((())()((()((()(()()())(()))((((()()((((((()((()(()(()((((()((()((())((((((()(()(())((((((()((((((((((()((())()))()(()(()(((((()()()))((())))()(()((((((((((((((()(((()((((()((())((()((()(((()()(()(((()((())(()()())))()(()(()(((((()()(()(()((((()(((((())()(()(()))(((((()()(((()()(())((((((((((((((())((())(((((((((((())()()()(())()(()(()(((((((((())(((()))(()()())(()((((()(())(((((()())(())((((((((())()((((()((((((())(()((()(())(((()((((()))(((((((((()()))((((()(())()()()(())(()((())((()()))()(((())(((((())((((((()()))(((((((((()((((((())))(((((((()((()(()(())))())(()(()))()(((((()())(()))()(()(())(((()))))())()())))(((((()))())()((()(()))))((()()()((((((()))()()((((((((())((()(()(((()(()((())((()())(()((((())(()(((()()()(()(()()))())())((((((((((())())((()))()((())(())(())))())()(()()(())))())(()))(((()(()()(((()(((())))()(((()(())()((((((())()))()))()((((((()(()(((((()())))()))))())()()(((()(((((())((()()(()((()((()(()(()(())))(()()()()((()(())(((()((()))((((()))())(())))())(()))()()()())()))(((()()())()((())))(())(()()()()(()())((()(()()((((())))((()((()(())((()(()((())()(()()(((()())()()())((()))((())(((()()(())))()()))(((()((())()(((((()())(())((())()())())((((((()(()(((((()))(()( 2 | -------------------------------------------------------------------------------- /input10.txt: -------------------------------------------------------------------------------- 1 | 1113222113 2 | -------------------------------------------------------------------------------- /input11.txt: -------------------------------------------------------------------------------- 1 | vzbxkghb 2 | -------------------------------------------------------------------------------- /input12.txt: -------------------------------------------------------------------------------- 1 | {"e":{"a":{"e":-39,"c":119,"a":{"c":65,"a":"orange","b":"green","d":"orange"},"g":"violet","b":{"e":6,"c":{"c":"violet","a":8,"b":["red",{"a":37},"green",84,"yellow","green",[24,45,"blue","blue",56,"yellow"],"orange"]},"a":"violet","b":{"a":85},"d":[109,66,["yellow","violet",21,-30],"violet","blue",-43,{"e":"violet","c":"red","a":"blue","b":-22,"d":[71,"red",30,"violet","red",26,120],"f":["red"]},"red"]},"d":{"e":"violet","a":"blue","d":"blue","c":"blue","h":"orange","b":{"e":"red","a":{"c":115,"a":137,"b":"green"},"d":-25,"c":"blue","h":{"a":161,"b":["yellow",56,129,-31,"yellow","red","green",105,"orange",130]},"b":142,"g":194,"f":122,"i":-16},"g":173,"f":["orange","green",54,-9],"i":-23},"f":{"c":110,"a":"yellow","b":[{"a":155},156,"violet",94,"yellow"],"d":{"e":91,"a":-18,"d":"red","c":["green","orange","orange",190,"yellow",158,"blue","orange","blue",4],"h":143,"b":"orange","g":145,"f":["orange",37,"yellow",-22,{"c":30,"a":78,"b":196,"d":84},-7,["yellow"]]}}},"b":[[{"c":0,"a":108,"b":"green","d":{"e":59,"c":119,"a":104,"b":167,"d":"blue"}},[189,"blue",121,[["green","orange","orange",-17,192,"red"],{"a":"violet"},"green",{"c":42,"a":"blue","b":"red"},{"e":78,"a":"blue","d":"violet","c":-9,"h":"violet","b":115,"g":"orange","f":"violet","i":"red"}],57,"violet"],"green"],[["blue",[1,53,"orange"],{"e":["green",-12,"blue","orange","green",136,173],"a":"violet","d":-43,"c":{"e":144,"c":133,"a":"yellow","g":154,"b":"orange","d":127,"f":194},"h":{"e":52,"a":-43,"d":"orange","c":-45,"h":"orange","b":150,"g":-12,"f":91,"i":6},"b":{"e":"yellow","c":"blue","a":"violet","g":112,"b":174,"d":"violet","f":90},"g":177,"f":"blue"},"red","violet",96],"green","violet",[{"a":["red","red",46,"red"],"b":["green",193,54,"orange"]},["orange",8,1,["violet",84,"violet"],155,"yellow",151,"blue",196],"yellow","red",{"a":["green","orange","green",61,"blue",39,-2,46,"red",54]},"violet",128]]]},"a":{"e":[{"e":["yellow"],"c":93,"a":"violet","b":{"a":{"a":"yellow","b":"blue"},"b":-4},"d":"violet"},171,103,[13,"orange",[[51,"violet","yellow",{"c":85,"a":103,"b":"green"},97,{"e":"orange","a":-11,"d":62,"j":"yellow","c":"orange","h":47,"b":83,"g":119,"f":180,"i":136},{"a":177},80],{"e":{"c":"yellow","a":"orange","b":3,"d":197},"a":130,"d":"red","j":"red","c":-44,"h":-15,"b":64,"g":125,"f":82,"i":"green"}],{"e":["orange",42,["orange",197,"violet","yellow","blue",11,"yellow"],189,"yellow","blue","green","violet"],"a":{"a":149,"b":69},"d":128,"c":[["green",150,45,86,"red",-8,41,"orange","blue"]],"h":[[-4,127,"yellow","violet",124,112,196,"violet",161,40],37,0,"orange",-30,-43,[-24,"orange",142,"violet","red"],"blue",66],"b":{"c":"violet","a":["yellow",91,182,20,"orange",159,46,55,141],"b":{"c":173,"a":-40,"b":"green","d":"violet"},"d":[67,80,27,-15]},"g":"red","f":{"c":"orange","a":99,"b":"green"}},{"e":{"c":40,"a":"orange","b":"green"},"c":"green","a":-44,"b":{"e":"blue","c":56,"a":"yellow","g":62,"b":188,"d":141,"f":-21},"d":"yellow","f":{"e":"yellow","c":67,"a":33,"g":"yellow","b":"yellow","d":51,"f":195}}],["orange","violet",["red"],["green",35,[170,-30,"orange",140,"green","violet","violet",["orange","yellow","yellow",35,"blue","violet",-36,182,"yellow",141],146]],{"a":61,"b":"orange"},[31,"blue","green",65,"red","green"],"violet"],{"c":"blue","a":["blue"],"b":17},95],"c":[[48,"blue",[49],"orange",{"e":"violet","c":"green","a":"red","b":"red","d":-29,"f":["orange",20,190,97,["orange","blue",-30,"blue","green"],"blue","yellow",-47,[123,"yellow","green"],-41]},"green",{"a":170,"b":32},[{"c":"green","a":"violet","b":"red"},["yellow",36,"yellow","violet",149,{"e":"red","c":141,"a":-24,"b":"yellow","d":-13,"f":"red"},69,"orange",19,[87,"red",167,"red",77,110]],"orange","violet"],{"a":-16}],[["red"],"violet"],{"a":[["red",83,{"e":"red","c":"blue","a":"blue","b":"orange","d":"orange"},49,"green","violet"],{"e":"yellow","a":"violet","d":17,"j":"green","c":{"e":"orange","c":"green","a":"green","b":99,"d":"yellow","f":"orange"},"h":9,"b":159,"g":"yellow","f":167,"i":147},["blue","green","violet"],"yellow",["violet",197,"blue",[170,81,"yellow","orange",196],-24,99,193],-8,["red",81,-11,"green","red","blue","yellow","blue",["blue","violet",131,184,160,-1]],"green"]},"orange"],"a":[{"e":"blue","a":"violet","d":[{"a":"blue","b":46},"violet",72,35,61,161],"j":["green",78,144,[168,["red",77,38,"green","red"],"green","yellow",-8,"yellow"],190,40,"yellow",17,171],"c":{"e":"red","c":"violet","a":"violet","b":-14,"d":"red","f":167},"h":[[[83,"green",69,"red"],"green",155,133],106,1,"orange"],"b":-41,"g":{"a":27},"f":"red","i":{"e":"green","c":"green","a":182,"g":"orange","b":"orange","d":["orange"],"f":"orange"}},"yellow","green",-26],"b":{"e":[-32,-11,{"e":"red","c":"yellow","a":{"e":"green","a":"red","d":105,"c":-20,"h":85,"b":{"e":47,"a":89,"d":"green","c":"violet","h":"orange","b":"green","g":140,"f":"green"},"g":111,"f":"orange","i":"yellow"},"b":143,"d":{"e":{"e":"orange","c":129,"a":"blue","b":142,"d":"violet"},"c":"blue","a":122,"b":["violet","orange",84,"orange"],"d":"red","f":"blue"}},58,[147]],"a":{"e":"orange","c":[{"e":141,"c":114,"a":137,"g":"orange","b":61,"d":105,"f":33}],"a":["red","red",{"e":"green","c":4,"a":"violet","b":"red","d":"blue"},"yellow",["green",15,"green",-40,149,"orange",{"e":-7,"c":74,"a":"red","b":"green","d":32}],"blue","yellow",146,[191,"blue",["orange","blue",187,"blue","orange",127,"yellow",38],120,161,55,-30,"green",-10,"violet"],"orange"],"b":{"a":-32,"b":"blue"},"d":{"e":["green",27],"c":[94,"violet","red",18,166,"yellow"],"a":{"e":"green","a":95,"d":"green","j":176,"c":84,"h":"violet","b":"yellow","g":-25,"f":51,"i":119},"b":144,"d":{"c":"violet","a":"yellow","b":"red"}}},"d":{"e":{"e":140,"a":{"e":"green","c":"green","a":0,"b":68,"d":152,"f":"red"},"d":["blue",6],"c":-29,"h":"green","b":["violet",106,"violet","orange",-38,175],"g":54,"f":[177,31,"violet","yellow"],"i":185},"a":"green","d":[111,49,"yellow","blue","orange",{"e":"yellow","a":"orange","d":"violet","j":"blue","c":"red","h":88,"b":-1,"g":"red","f":"red","i":{"e":121,"a":112,"d":195,"j":103,"c":94,"h":"red","b":12,"g":8,"f":22,"i":"orange"}},64,["violet",["blue",76,"blue","red","red"],["violet","blue","orange","yellow",144],185,{"a":66,"b":"orange"},199,"green","green"],14],"c":{"e":"green","a":"orange","d":{"c":[-23,189,-11,"green","violet",178,-4,"blue",68,"violet"],"a":["orange","red"],"b":"yellow","d":"yellow"},"j":{"c":-33,"a":"blue","b":"violet"},"c":107,"h":{"e":-16,"a":174,"d":{"e":"orange","c":"green","a":-28,"b":-30,"d":73},"j":"yellow","c":"orange","h":"orange","b":["blue","violet",-4,76,"red","red"],"g":59,"f":12,"i":199},"b":{"a":"green","b":54},"g":"violet","f":174,"i":["orange",41,85,"yellow","green",25,"red",-20,156,143]},"h":"yellow","b":"red","g":90,"f":-37,"i":{"a":146,"b":"violet"}},"j":"blue","c":[1,["yellow",-11,"green",66,"red",90,"green","yellow",3,{"e":-34,"a":194,"d":"green","c":[-11,"yellow"],"h":59,"b":"yellow","g":"blue","f":162,"i":"violet"}],81,158,170],"h":"blue","b":"green","g":["violet",["blue","blue"]],"f":[-44,"yellow",[35,[122,"red","yellow",{"a":"red","b":"violet"},"blue","orange","violet"],"violet",{"e":-48,"a":6,"d":-6,"c":4,"h":"yellow","b":"blue","g":"red","f":"red"}],[{"e":-2,"a":156,"d":"red","j":69,"c":0,"h":"violet","b":"orange","g":61,"f":102,"i":["orange","blue","violet",-1,137]},{"a":183,"b":89}],{"a":167,"b":"orange"},193,95,[97,[66,154,-32,"orange",121,{"e":198,"a":"blue","d":102,"c":"red","h":"green","b":135,"g":"orange","f":-49,"i":151},97,7,"red"],195,"blue",49,"green",10]],"i":["violet",1,{"e":"orange","c":196,"a":"blue","g":"red","b":190,"d":87,"f":128},"blue",128,147]},"d":[[{"a":"green","b":43},169,-8,"orange",{"a":["violet",["red","violet","orange","yellow",-49,"violet",-25],"violet",60,33,"violet",["yellow","orange",31,144,"red","yellow",73,"orange","red","green"],["green",-31,"red"],"orange","blue"]},"violet","blue"],40,154,{"a":{"c":"violet","a":145,"b":166,"d":["blue",["blue",125,185,"yellow","red",152,89,-18,"blue",141],26,2,35,"orange",190]}},170,"violet",-31,[[151,"orange","green",["blue",114,-5,"yellow"],"blue","green","orange","yellow",62,{"c":22,"a":"green","b":"blue"}],17,[176],"violet",129,67,{"c":{"c":"red","a":140,"b":25},"a":["blue","green",163],"b":30,"d":[60,"green","red",126,[48,"green"],-26,["yellow","green",150,"red","violet","red","violet",59,-12],167,"yellow"]},"yellow","yellow"],"blue"]},"d":{"c":"green","a":52,"b":[136,{"c":{"a":[197,["orange","red",138,67,"orange",172,2,"orange"],"red"]},"a":"violet","b":{"a":{"e":172,"c":171,"a":"yellow","b":191,"d":{"e":171,"a":"red","d":"violet","c":"green","h":"yellow","b":"yellow","g":73,"f":"yellow"}}},"d":[86,-11,-5,["orange","green",64,["blue",15,"orange","yellow","violet",181,"green","blue"],"yellow","yellow",{"e":27,"c":156,"a":"blue","g":"violet","b":38,"d":51,"f":23},"orange","violet"],10]},[55,{"e":191,"c":"blue","a":"orange","b":"yellow","d":109},"blue",{"c":164,"a":[198,-9,183,{"e":14,"a":176,"d":117,"c":"violet","h":"violet","b":-44,"g":"violet","f":"red","i":"orange"},"yellow",0],"b":58,"d":33},"red",[125,23,"blue",149,[["blue",-44,22,133,"orange","yellow","yellow","violet","violet",131],"violet",-1,"red",66,"blue"],"green","red","red",[-31,"blue",["orange","orange","yellow",44,"green","yellow","green",160,"violet"],"yellow",["orange","violet","green","violet",194,"blue",-27],"green",{"e":"violet","a":"red","d":67,"c":68,"h":"blue","b":"orange","g":"orange","f":"violet","i":"violet"},"yellow"]],"violet",[59,158,{"e":"blue","c":"blue","a":"orange","g":73,"b":97,"d":"red","f":"orange"}],["red",[31,[95,72,"orange","yellow"],"blue",192,63],[197,"green",{"e":112,"a":"violet","d":"blue","c":-2,"h":"blue","b":"green","g":124,"f":"blue"},177,"green","blue",162,107]]],43,[{"e":"red","c":{"e":["green",-33,11,154,"yellow",-4],"c":"yellow","a":[7,"orange","orange","yellow",118,169,"red","blue"],"b":"green","d":114},"a":{"e":"green","a":"green","d":187,"j":{"e":106,"c":-41,"a":"violet","b":173,"d":12},"c":"red","h":"violet","b":-4,"g":{"c":"violet","a":-26,"b":87,"d":-33},"f":"green","i":-46},"b":"green","d":13,"f":"yellow"}],["blue","violet","orange","red",{"e":"green","a":["violet",140,[76,"green",94,33,"green",31,"orange",53],"violet","yellow","violet","blue",["blue",196,"orange","yellow","orange",-42,"orange",171,-47,"violet"],"green",110],"d":31,"c":"orange","h":{"e":-45,"a":"green","d":["violet"],"c":"red","h":105,"b":130,"g":-36,"f":"orange","i":{"e":"red","c":137,"a":54,"g":"blue","b":"violet","d":102,"f":178}},"b":-41,"g":{"e":6,"a":-25,"d":66,"j":"violet","c":39,"h":30,"b":63,"g":46,"f":56,"i":"blue"},"f":6,"i":"violet"},[84,175,"orange",{"a":"green"},"green",66,{"e":"red","a":{"a":178,"b":"yellow"},"d":"yellow","c":["red","red",38,"orange","blue",136,"red",137,"red"],"h":163,"b":["orange",84,"red",178],"g":65,"f":"blue"}],[98,"yellow",[46,"orange","yellow","yellow"],"blue",151,189,["yellow",{"e":"orange","a":27,"d":45,"c":48,"h":"green","b":90,"g":180,"f":-43},"yellow"],"blue"],{"a":"green"},"blue",{"c":37,"a":{"e":59,"c":["blue"],"a":"yellow","g":38,"b":"blue","d":"violet","f":"orange"},"b":"orange","d":"violet"}],{"c":75,"a":{"e":{"a":130},"a":5,"d":1,"c":72,"h":{"e":"red","a":11,"d":157,"c":97,"h":-24,"b":"red","g":111,"f":21},"b":{"e":145,"a":"red","d":"violet","j":[-11,191,-43,"blue","orange",105,158],"c":"red","h":143,"b":{"e":"orange","c":"yellow","a":-31,"g":177,"b":"violet","d":"blue","f":"green"},"g":"green","f":48,"i":{"e":18,"a":142,"d":"yellow","c":116,"h":"violet","b":135,"g":37,"f":36}},"g":-26,"f":[186,192,"orange",117,-9,"violet",-19,55,"green",167],"i":"green"},"b":"yellow","d":{"a":138}}]},"c":"blue","h":[[19],"orange",[{"e":["yellow",68,28,29,{"e":"red","a":"violet","d":"green","c":143,"h":"red","b":"orange","g":44,"f":123,"i":"orange"},38,28,65,{"e":-26,"c":["red",132,"red",124,"yellow",115],"a":170,"g":"yellow","b":"green","d":-18,"f":{"c":1,"a":"red","b":-1}}],"a":"orange","d":129,"c":33,"h":"violet","b":"orange","g":"green","f":-24},["violet",-22],[64,-20,{"e":46,"a":76,"d":97,"c":-21,"h":98,"b":"violet","g":{"e":-7,"c":"violet","a":190,"b":"violet","d":138,"f":"violet"},"f":[178,"blue","blue"],"i":"red"},{"e":"orange","c":"red","a":{"e":"orange","a":["green"],"d":[19,"red"],"c":-32,"h":-15,"b":"yellow","g":116,"f":"blue","i":"orange"},"b":96,"d":"green","f":176},[[104,99,"yellow",-13,"red",{"c":"blue","a":"red","b":46,"d":60},-13,9],-22,-26,133,["green",["red",188,"green","green"],166,"yellow",{"e":"yellow","c":197,"a":65,"b":83,"d":-19,"f":"yellow"},[157,"violet","blue","yellow",-30,"violet",-3],21,{"a":-15}],43,["orange","blue",88,"yellow",103,31],"orange",-24]],{"c":"violet","a":{"a":26,"b":"yellow"},"b":["violet","violet",{"e":102,"a":"red","d":178,"j":187,"c":"orange","h":"violet","b":72,"g":-37,"f":"violet","i":"orange"},44,114,"yellow",85]}],{"e":150,"c":"green","a":{"e":{"e":{"e":{"e":"orange","a":48,"d":41,"j":"orange","c":"orange","h":30,"b":"yellow","g":41,"f":-40,"i":8},"c":199,"a":32,"b":"yellow","d":-28},"a":46,"d":[50,"red","violet",63,"red",56,-18,"orange","violet","red"],"c":"blue","h":{"e":"green","c":172,"a":"green","b":-30,"d":22,"f":"yellow"},"b":"orange","g":65,"f":"yellow","i":174},"a":"green","d":[196,{"e":{"e":176,"a":"violet","d":"orange","j":-37,"c":19,"h":31,"b":155,"g":"red","f":106,"i":"green"},"c":"red","a":64,"b":"orange","d":179,"f":8},"yellow",103,"violet",{"e":142,"a":111,"d":"yellow","c":"violet","h":"red","b":148,"g":29,"f":179,"i":"green"},-26],"c":-19,"h":["red",134,"green","green",105],"b":"orange","g":126,"f":76,"i":158},"b":55,"d":"green"},[[[61],[["orange","red"],[151,"yellow",127,"yellow",185,"yellow",{"e":105,"c":"yellow","a":198,"b":"orange","d":"blue","f":89},140,{"e":"violet","a":-15,"d":169,"j":3,"c":"yellow","h":74,"b":-41,"g":29,"f":112,"i":18}]],101,{"e":[45,"green","yellow","blue","violet",["violet","yellow",159,0,"orange","yellow",100,"green","blue",49],[5,-37],"blue","orange"],"c":88,"a":"blue","b":-32,"d":23},77,{"e":["yellow",119,197,["orange",-28,"yellow",179,130,74,-10,115,"violet",79],"orange",63,-15,17,"blue","violet"],"c":{"e":164,"a":83,"d":"yellow","c":119,"h":"yellow","b":148,"g":-22,"f":[-17,17,"violet","green","red"],"i":67},"a":{"e":54,"a":147,"d":"yellow","c":86,"h":113,"b":"yellow","g":77,"f":101,"i":"blue"},"g":"orange","b":[193,"orange","orange","red",39,44,43,-29],"d":"violet","f":191}],"orange",["red","violet","yellow",["red",54,{"e":{"a":41,"b":"violet"},"c":"red","a":{"e":"red","a":"yellow","d":"green","j":-33,"c":96,"h":137,"b":"yellow","g":30,"f":"green","i":"blue"},"b":181,"d":"violet","f":"green"},49,"yellow"],"orange","yellow",{"e":"orange","c":[46,"orange",["blue","green","blue","yellow","yellow","violet","orange","orange",1],"yellow",155,194,"yellow",149],"a":"green","b":-3,"d":153,"f":[-21,-26,-25,"blue","red",108,169,["green",100,43],51,-9]}],71,[[[{"a":"violet","b":27},148,109,["blue",60,47,"violet","yellow",-47,"violet"],"red",{"e":97,"c":-21,"a":"yellow","b":"green","d":126},"yellow",85,89],{"a":["red","orange","violet","blue","blue","blue",128,"blue"]},{"e":-48,"c":{"c":90,"a":"orange","b":"yellow"},"a":"yellow","b":"red","d":172},"yellow",{"a":"orange"},[{"e":"yellow","a":40,"d":-9,"j":"violet","c":153,"h":79,"b":"violet","g":178,"f":2,"i":"yellow"},"green",-29],"red",-9,[9,{"a":39,"b":"green"},5,"violet",26,{"e":167,"c":"blue","a":"yellow","b":90,"d":33},"green",88,12,"blue"]],"red",{"c":{"e":"yellow","a":-44,"d":62,"j":-19,"c":96,"h":"green","b":-12,"g":"green","f":"red","i":134},"a":22,"b":24,"d":33},"red","violet",{"e":181,"c":64,"a":"violet","g":"green","b":"yellow","d":"violet","f":101},"green",[132,93,[-6,[-3,28,"red"],-21,"red","violet",{"a":180},"red","blue",-15],{"e":171,"a":{"e":"green","c":49,"a":"orange","g":22,"b":"violet","d":"orange","f":"orange"},"d":"red","c":113,"h":"green","b":[30,"blue"],"g":{"a":139,"b":47},"f":"red","i":"red"},"violet",158,"green",5,-1],19],"red"],{"e":{"c":["orange",93,162,"green","violet",["green",178],{"a":"green","b":{"e":-12,"a":-16,"d":144,"c":"red","h":"violet","b":43,"g":"green","f":-42}}],"a":"blue","b":"blue","d":{"e":["orange","red",{"c":-19,"a":"green","b":93},"yellow","green","orange","orange","red","green"],"a":"green","d":{"e":"yellow","a":2,"d":"violet","j":"green","c":"blue","h":19,"b":"violet","g":"blue","f":[157,"green",109,59,"red",74,"red","blue","green"],"i":"orange"},"j":"yellow","c":166,"h":"yellow","b":"yellow","g":["violet",138,["violet",141,"green"]],"f":28,"i":{"e":52,"c":"yellow","a":"green","b":5,"d":{"e":153,"a":"yellow","d":191,"j":"green","c":"green","h":124,"b":"green","g":181,"f":134,"i":"yellow"},"f":193}}},"c":"violet","a":{"a":{"a":"green"},"b":[132]},"b":[{"e":11,"a":"green","d":{"e":{"e":119,"a":"violet","d":"red","c":"red","h":"violet","b":-6,"g":"blue","f":"orange","i":"orange"},"a":183,"d":[-36,"yellow"],"c":"red","h":71,"b":"yellow","g":2,"f":"orange"},"c":"green","h":"yellow","b":29,"g":"green","f":"blue","i":{"e":"yellow","a":-24,"d":[55,125,193,70,60,190,199],"c":"green","h":[49,"yellow","yellow",74,"red",163],"b":198,"g":50,"f":"blue","i":70}},"orange"],"d":"blue"},{"c":{"e":-20,"a":8,"d":["orange",157,152,"green",46,"green",7,89,"violet",[-22,-49,81,127]],"c":35,"h":["blue","yellow","orange",94,"orange","yellow"],"b":"red","g":{"a":"green","b":["yellow","orange",198]},"f":"violet","i":17},"a":-48,"b":"blue"}],"b":[[149,[{"e":"blue","c":-30,"a":"violet","g":"violet","b":"yellow","d":178,"f":-4}],"orange",131,"yellow",{"a":"red","b":"violet"},"blue"],[11],{"e":[35,118,{"e":39,"a":"yellow","d":[119,"orange",120,-43],"j":"violet","c":"orange","h":"blue","b":-32,"g":[{"e":"green","c":106,"a":144,"b":147,"d":"green"},"violet","orange"],"f":116,"i":"orange"},112,"yellow"],"a":{"e":19,"a":"orange","d":61,"c":"red","h":"blue","b":164,"g":{"c":"red","a":-10,"b":{"e":{"e":"green","c":82,"a":103,"g":67,"b":153,"d":"violet","f":22},"c":-22,"a":101,"b":71,"d":{"a":152,"b":"green"},"f":"orange"}},"f":157,"i":{"e":"green","a":"orange","d":-8,"j":[159,73,182,"red","green"],"c":13,"h":"blue","b":"yellow","g":186,"f":"orange","i":81}},"d":13,"c":[186,["yellow",["violet","violet"],"green",-28],54,["blue",[119,"red",119,91,181],117],-15,190,{"c":"red","a":13,"b":[{"c":"green","a":70,"b":8,"d":175},"orange","green","yellow","green"]},"blue",-43],"h":{"e":[{"a":"green"},88,"red","violet",10],"a":{"a":"orange","b":[62,"yellow","green"]},"d":151,"c":"red","h":"orange","b":126,"g":{"a":"orange"},"f":"orange","i":46},"b":[[-2,"violet","violet","red",{"a":192},"green",122],["orange","red",{"c":62,"a":52,"b":-45},{"e":{"a":"violet","b":-45},"a":"red","d":"orange","c":"yellow","h":{"e":67,"c":-27,"a":116,"b":"violet","d":"green","f":-18},"b":"yellow","g":"blue","f":"blue"},27,{"c":37,"a":-39,"b":"blue"}],107,"yellow",["blue","red",143],"blue",{"e":"orange","a":["yellow",["blue",8,149,141,"red",-28,"red"],18],"d":29,"c":"violet","h":-21,"b":[{"e":66,"c":"green","a":"blue","b":-29,"d":"orange","f":"violet"},"blue",-21],"g":"green","f":112},73],"g":["red",{"a":{"e":93,"a":13,"d":"violet","c":175,"h":158,"b":9,"g":194,"f":-10},"b":"blue"}],"f":130}],"g":[["red","orange","orange",172,154,{"e":{"a":"blue","b":{"a":"yellow","b":53}},"c":-11,"a":"orange","g":"yellow","b":{"e":{"e":94,"a":123,"d":184,"j":-4,"c":193,"h":152,"b":"blue","g":"red","f":101,"i":178},"c":"blue","a":178,"b":154,"d":[103,109,190,"yellow",29,"red","orange","yellow",79,"green"],"f":"orange"},"d":{"e":25,"a":{"a":"blue"},"d":"green","c":"orange","h":{"e":144,"c":["red","blue","violet",15,"green",109,72],"a":"yellow","b":"orange","d":"yellow"},"b":151,"g":[141,"orange",134,"blue","blue",4,21,"blue","green"],"f":96},"f":"blue"},"blue"],80,186,[[194,"violet",70,"green"],{"a":"orange","b":"green"},[{"e":"orange","a":179,"d":{"e":164,"c":-14,"a":"blue","g":"yellow","b":"violet","d":76,"f":-33},"c":"green","h":"violet","b":"orange","g":"blue","f":"orange","i":"green"},"blue"]],"orange","yellow",66],"f":{"a":["violet"],"b":87},"i":{"e":{"c":[{"e":"red","a":19,"d":100,"j":"red","c":"red","h":"red","b":"yellow","g":-41,"f":10,"i":"blue"},42,92,"violet","red",[149,"green",91,"blue"],-33,["green",73,129],110,{"e":168,"c":153,"a":-30,"b":"yellow","d":[192,{"c":"blue","a":"blue","b":-16,"d":-18},{"e":"red","c":"yellow","a":"violet","b":31,"d":"green"},"blue"],"f":{"c":9,"a":"yellow","b":-16,"d":128}}],"a":[[["green","violet",136,59,"orange",173,116,113,"yellow"],"green",{"e":"blue","c":"green","a":"blue","g":"red","b":98,"d":-25,"f":21},"orange",184],4,"yellow","red",-24,{"c":"orange","a":15,"b":{"e":109,"c":179,"a":61,"b":"orange","d":190,"f":9}}],"b":[[92,148,{"e":"blue","a":0,"d":108,"c":197,"h":"red","b":"orange","g":-22,"f":105,"i":"blue"},"blue"],-7,149]},"a":{"e":{"a":{"e":"green","a":["violet",172],"d":-10,"c":42,"h":"blue","b":80,"g":{"e":"red","c":"orange","a":"yellow","g":87,"b":{"e":31,"c":129,"a":"orange","b":43,"d":"blue"},"d":"blue","f":81},"f":"violet"},"b":"orange"},"a":182,"d":{"c":{"a":154},"a":"blue","b":{"e":31,"a":["yellow","blue","red",{"a":"orange"},"red",62,39,"red",["green","orange","yellow",47,"orange",55,"blue"]],"d":[72,187,"red","orange",59,"yellow","violet","green"],"j":"orange","c":"yellow","h":185,"b":{"e":"blue","c":"violet","a":["orange",7,180,150,46,"yellow",176,"orange"],"b":148,"d":"blue"},"g":"blue","f":"yellow","i":102}},"c":"red","h":-9,"b":14,"g":{"a":"green","b":{"c":-18,"a":81,"b":104}},"f":[[{"e":-33,"c":"green","a":"orange","b":"blue","d":"blue"},"yellow",141,[42,197],[-12,61,{"e":"violet","a":"violet","d":"green","c":-21,"h":-5,"b":"orange","g":39,"f":"green"},"blue"],31,[[101,"blue",-14,"red",88],58,["red","blue","violet",34],-14,"yellow",98,106,91,131],"yellow",[151,"red","green",{"e":"violet","c":"green","a":49,"g":155,"b":96,"d":"blue","f":"orange"},-18,184,{"c":"blue","a":1,"b":162},{"e":115,"a":94,"d":97,"j":-34,"c":"blue","h":115,"b":"red","g":"orange","f":149,"i":105}],38],{"c":{"e":"blue","c":90,"a":"yellow","b":142,"d":"violet"},"a":-38,"b":"violet"}],"i":189},"d":"orange","c":[[103,8,"green",13,23,"violet",55],[{"e":79,"c":74,"a":{"e":"violet","a":{"c":"red","a":"violet","b":168},"d":142,"j":"blue","c":173,"h":"yellow","b":"green","g":"blue","f":"blue","i":"blue"},"g":[{"c":"violet","a":82,"b":90},-24,{"a":"orange"},"yellow",[126,53,153,6],52,137,"violet",181],"b":105,"d":166,"f":{"e":"blue","c":-35,"a":"blue","b":188,"d":-14,"f":63}},{"e":95,"a":"green","d":"yellow","j":"red","c":81,"h":107,"b":-46,"g":162,"f":"green","i":"red"},[{"e":"violet","a":150,"d":126,"c":10,"h":{"e":"green","a":"orange","d":19,"c":"green","h":"green","b":79,"g":"red","f":"yellow","i":"blue"},"b":{"a":25,"b":147},"g":180,"f":126},{"e":-48,"a":192,"d":-45,"c":25,"h":"green","b":{"c":165,"a":"orange","b":"red","d":"blue"},"g":"green","f":-24},95,{"e":"blue","a":"violet","d":"yellow","j":"blue","c":44,"h":["blue","green","red",142,"red"],"b":[-43,"violet","green",53],"g":33,"f":"orange","i":196},"orange","green",43,[113,"violet","orange",129,{"c":6,"a":"violet","b":"green","d":"green"},20]],"green"]],"h":{"a":-11},"b":{"e":"violet","c":174,"a":"violet","g":[{"e":105,"a":{"c":-5,"a":177,"b":63},"d":-41,"c":80,"h":[110,109,113,"blue"],"b":-28,"g":"red","f":129},["green",[108],{"a":4},[182,96,29,[181,14,"yellow","violet"],13,{"e":132,"a":115,"d":"red","c":"violet","h":"violet","b":"violet","g":"green","f":"green"},{"e":"orange","a":"yellow","d":"blue","j":"red","c":137,"h":"violet","b":"green","g":-22,"f":"yellow","i":-12},"green","yellow",57],-44,{"a":88,"b":-3},22,{"c":"red","a":"violet","b":-21}],[[14,"orange"]],-36,128,"yellow",[-47,[-7,36,177],"blue","blue",["yellow","violet",-23,"violet",-40,"orange",{"e":129,"a":21,"d":51,"j":"violet","c":"red","h":15,"b":174,"g":191,"f":101,"i":105}],23,[-47,[133,66,"violet"],177,"violet","yellow","green",159,"yellow"]],{"e":[{"a":"orange"},"green",69,"orange",43,"violet","violet",192,140,"green"],"a":62,"d":"violet","j":{"c":"violet","a":-25,"b":"violet"},"c":120,"h":"red","b":{"a":13},"g":"green","f":124,"i":33},[[19,176,174,"orange","violet","violet",105,128,"red"],{"a":10,"b":"red"},["orange",37,187,"green",176],"blue","red",[153,"yellow","violet",137,"orange","blue",[70,"red",174,"blue","green","yellow",99,"red"],"violet","violet","red"]]],"b":[{"c":133,"a":"orange","b":98,"d":{"c":"red","a":-9,"b":103}},"blue",[155,"yellow"],[["yellow",-8,{"e":"blue","c":59,"a":71,"g":"orange","b":88,"d":"orange","f":17},"blue",-37],{"e":82,"c":"violet","a":99,"b":81,"d":"yellow","f":161},"blue",{"c":-7,"a":154,"b":"violet"},-9,-13,53,{"e":"violet","a":"yellow","d":-26,"c":179,"h":"green","b":"red","g":-24,"f":133,"i":-36}]],"d":{"e":[9,[49],28,"red",{"c":23,"a":157,"b":{"c":"violet","a":"green","b":-11,"d":"green"},"d":139},"orange","green",93,44,[-19]],"a":-6,"d":7,"c":{"e":{"c":"violet","a":-21,"b":12},"c":["green",[-23,-40,157],"red",["orange","blue"],"violet","red",85,"violet","yellow",150],"a":162,"g":"yellow","b":"green","d":["green","yellow",181,"green",-2,{"e":"red","a":"yellow","d":129,"c":-34,"h":129,"b":152,"g":"yellow","f":80,"i":"red"},"green","red",-9,"red"],"f":6},"h":{"e":136,"a":"violet","d":["violet",-15,129,"green",5,"green",[-28,156,141,"blue",22,"green",34],"green"],"c":149,"h":["violet"],"b":149,"g":"green","f":149},"b":{"e":123,"a":"red","d":{"e":0,"c":"green","a":"violet","b":"yellow","d":"red","f":"green"},"c":{"e":{"e":"yellow","c":"red","a":"red","b":"violet","d":"yellow"},"a":"yellow","d":{"e":-39,"a":-11,"d":63,"c":179,"h":4,"b":44,"g":"orange","f":"violet","i":"yellow"},"c":-43,"h":"green","b":"violet","g":"blue","f":"yellow","i":124},"h":48,"b":129,"g":["orange",147,174,"blue","green",115],"f":172,"i":-36},"g":"red","f":30,"i":"violet"},"f":"red"},"g":{"e":{"e":[[126,"orange",196,"orange","red",{"e":23,"a":"yellow","d":128,"c":12,"h":-49,"b":"green","g":"yellow","f":41,"i":45},"red","violet"]],"c":[["red",103,{"e":69,"a":"violet","d":"yellow","c":"green","h":"red","b":133,"g":25,"f":"violet"}],88,"green","red",-29,"red"],"a":37,"b":"green","d":{"e":"orange","c":{"e":{"e":109,"c":144,"a":"yellow","b":70,"d":83},"c":-3,"a":"green","b":"yellow","d":146},"a":86,"b":-1,"d":{"a":68}}},"c":{"c":[155,18,"blue",-16,"orange",-36,49,"red",["yellow",136,140,-10,11,"violet","red",134,156,"violet"]],"a":64,"b":{"e":"violet","c":193,"a":101,"b":["green"],"d":182,"f":86},"d":[198]},"a":"yellow","g":"violet","b":1,"d":-27,"f":"orange"},"f":{"e":20,"c":{"e":155,"c":{"c":[181,{"e":-32,"a":"orange","d":"orange","j":"yellow","c":66,"h":-39,"b":"violet","g":"violet","f":"red","i":23},4,"blue",70,"violet","blue",141,{"a":"yellow","b":184},"violet"],"a":160,"b":158,"d":197},"a":138,"g":[48],"b":26,"d":11,"f":{"c":"yellow","a":179,"b":"red","d":90}},"a":148,"g":"yellow","b":[[{"a":["yellow"]},"yellow",19,"green",39],{"c":{"a":"blue"},"a":{"e":41,"c":191,"a":173,"b":"green","d":-14,"f":19},"b":{"a":["orange",4,48],"b":193},"d":"green"},["yellow",{"e":"orange","a":"orange","d":"blue","c":-39,"h":28,"b":"yellow","g":"red","f":"orange","i":[116,"red",173,76,24,-1,"green",101,-10]},70,{"c":"violet","a":44,"b":"violet","d":36},128,{"c":"yellow","a":"red","b":["yellow",-10]},-10,6]],"d":"violet","f":{"e":"violet","c":5,"a":"violet","g":173,"b":100,"d":["violet",194,{"e":["blue",181,"violet","yellow","blue",-7,137,43,112],"c":-19,"a":120,"b":"green","d":165},-1,195,"green",104],"f":128}}}} 2 | -------------------------------------------------------------------------------- /input13.txt: -------------------------------------------------------------------------------- 1 | Alice would gain 2 happiness units by sitting next to Bob. 2 | Alice would gain 26 happiness units by sitting next to Carol. 3 | Alice would lose 82 happiness units by sitting next to David. 4 | Alice would lose 75 happiness units by sitting next to Eric. 5 | Alice would gain 42 happiness units by sitting next to Frank. 6 | Alice would gain 38 happiness units by sitting next to George. 7 | Alice would gain 39 happiness units by sitting next to Mallory. 8 | Bob would gain 40 happiness units by sitting next to Alice. 9 | Bob would lose 61 happiness units by sitting next to Carol. 10 | Bob would lose 15 happiness units by sitting next to David. 11 | Bob would gain 63 happiness units by sitting next to Eric. 12 | Bob would gain 41 happiness units by sitting next to Frank. 13 | Bob would gain 30 happiness units by sitting next to George. 14 | Bob would gain 87 happiness units by sitting next to Mallory. 15 | Carol would lose 35 happiness units by sitting next to Alice. 16 | Carol would lose 99 happiness units by sitting next to Bob. 17 | Carol would lose 51 happiness units by sitting next to David. 18 | Carol would gain 95 happiness units by sitting next to Eric. 19 | Carol would gain 90 happiness units by sitting next to Frank. 20 | Carol would lose 16 happiness units by sitting next to George. 21 | Carol would gain 94 happiness units by sitting next to Mallory. 22 | David would gain 36 happiness units by sitting next to Alice. 23 | David would lose 18 happiness units by sitting next to Bob. 24 | David would lose 65 happiness units by sitting next to Carol. 25 | David would lose 18 happiness units by sitting next to Eric. 26 | David would lose 22 happiness units by sitting next to Frank. 27 | David would gain 2 happiness units by sitting next to George. 28 | David would gain 42 happiness units by sitting next to Mallory. 29 | Eric would lose 65 happiness units by sitting next to Alice. 30 | Eric would gain 24 happiness units by sitting next to Bob. 31 | Eric would gain 100 happiness units by sitting next to Carol. 32 | Eric would gain 51 happiness units by sitting next to David. 33 | Eric would gain 21 happiness units by sitting next to Frank. 34 | Eric would gain 55 happiness units by sitting next to George. 35 | Eric would lose 44 happiness units by sitting next to Mallory. 36 | Frank would lose 48 happiness units by sitting next to Alice. 37 | Frank would gain 91 happiness units by sitting next to Bob. 38 | Frank would gain 8 happiness units by sitting next to Carol. 39 | Frank would lose 66 happiness units by sitting next to David. 40 | Frank would gain 97 happiness units by sitting next to Eric. 41 | Frank would lose 9 happiness units by sitting next to George. 42 | Frank would lose 92 happiness units by sitting next to Mallory. 43 | George would lose 44 happiness units by sitting next to Alice. 44 | George would lose 25 happiness units by sitting next to Bob. 45 | George would gain 17 happiness units by sitting next to Carol. 46 | George would gain 92 happiness units by sitting next to David. 47 | George would lose 92 happiness units by sitting next to Eric. 48 | George would gain 18 happiness units by sitting next to Frank. 49 | George would gain 97 happiness units by sitting next to Mallory. 50 | Mallory would gain 92 happiness units by sitting next to Alice. 51 | Mallory would lose 96 happiness units by sitting next to Bob. 52 | Mallory would lose 51 happiness units by sitting next to Carol. 53 | Mallory would lose 81 happiness units by sitting next to David. 54 | Mallory would gain 31 happiness units by sitting next to Eric. 55 | Mallory would lose 73 happiness units by sitting next to Frank. 56 | Mallory would lose 89 happiness units by sitting next to George. 57 | -------------------------------------------------------------------------------- /input14.txt: -------------------------------------------------------------------------------- 1 | Vixen can fly 19 km/s for 7 seconds, but then must rest for 124 seconds. 2 | Rudolph can fly 3 km/s for 15 seconds, but then must rest for 28 seconds. 3 | Donner can fly 19 km/s for 9 seconds, but then must rest for 164 seconds. 4 | Blitzen can fly 19 km/s for 9 seconds, but then must rest for 158 seconds. 5 | Comet can fly 13 km/s for 7 seconds, but then must rest for 82 seconds. 6 | Cupid can fly 25 km/s for 6 seconds, but then must rest for 145 seconds. 7 | Dasher can fly 14 km/s for 3 seconds, but then must rest for 38 seconds. 8 | Dancer can fly 3 km/s for 16 seconds, but then must rest for 37 seconds. 9 | Prancer can fly 25 km/s for 6 seconds, but then must rest for 143 seconds. 10 | -------------------------------------------------------------------------------- /input15.txt: -------------------------------------------------------------------------------- 1 | Sugar: capacity 3, durability 0, flavor 0, texture -3, calories 2 2 | Sprinkles: capacity -3, durability 3, flavor 0, texture 0, calories 9 3 | Candy: capacity -1, durability 0, flavor 4, texture 0, calories 1 4 | Chocolate: capacity 0, durability 0, flavor -2, texture 2, calories 8 5 | -------------------------------------------------------------------------------- /input16.txt: -------------------------------------------------------------------------------- 1 | Sue 1: goldfish: 9, cars: 0, samoyeds: 9 2 | Sue 2: perfumes: 5, trees: 8, goldfish: 8 3 | Sue 3: pomeranians: 2, akitas: 1, trees: 5 4 | Sue 4: goldfish: 10, akitas: 2, perfumes: 9 5 | Sue 5: cars: 5, perfumes: 6, akitas: 9 6 | Sue 6: goldfish: 10, cats: 9, cars: 8 7 | Sue 7: trees: 2, samoyeds: 7, goldfish: 10 8 | Sue 8: cars: 8, perfumes: 6, goldfish: 1 9 | Sue 9: cats: 4, pomeranians: 0, trees: 0 10 | Sue 10: trees: 2, children: 10, samoyeds: 10 11 | Sue 11: akitas: 10, perfumes: 4, vizslas: 1 12 | Sue 12: akitas: 1, trees: 0, goldfish: 3 13 | Sue 13: perfumes: 6, goldfish: 10, cars: 8 14 | Sue 14: cats: 8, akitas: 5, vizslas: 0 15 | Sue 15: cars: 8, trees: 3, samoyeds: 5 16 | Sue 16: vizslas: 6, cats: 6, pomeranians: 10 17 | Sue 17: akitas: 6, cats: 2, perfumes: 9 18 | Sue 18: children: 9, goldfish: 2, akitas: 10 19 | Sue 19: trees: 3, perfumes: 0, goldfish: 6 20 | Sue 20: vizslas: 3, akitas: 0, trees: 1 21 | Sue 21: vizslas: 3, cars: 7, akitas: 3 22 | Sue 22: perfumes: 7, children: 1, pomeranians: 7 23 | Sue 23: trees: 10, cars: 9, akitas: 10 24 | Sue 24: akitas: 5, goldfish: 6, vizslas: 6 25 | Sue 25: samoyeds: 3, trees: 8, vizslas: 5 26 | Sue 26: vizslas: 4, pomeranians: 2, trees: 1 27 | Sue 27: cars: 9, goldfish: 2, trees: 4 28 | Sue 28: vizslas: 6, goldfish: 10, perfumes: 7 29 | Sue 29: vizslas: 6, pomeranians: 3, akitas: 6 30 | Sue 30: trees: 0, samoyeds: 5, akitas: 9 31 | Sue 31: vizslas: 1, perfumes: 0, trees: 6 32 | Sue 32: cars: 7, vizslas: 1, children: 10 33 | Sue 33: vizslas: 1, cars: 1, perfumes: 7 34 | Sue 34: vizslas: 9, trees: 10, akitas: 9 35 | Sue 35: akitas: 3, vizslas: 5, cars: 10 36 | Sue 36: cats: 3, children: 9, samoyeds: 3 37 | Sue 37: vizslas: 5, pomeranians: 7, cars: 6 38 | Sue 38: cars: 10, akitas: 5, vizslas: 8 39 | Sue 39: akitas: 5, trees: 9, children: 2 40 | Sue 40: vizslas: 0, cats: 7, akitas: 0 41 | Sue 41: cars: 9, trees: 10, perfumes: 8 42 | Sue 42: akitas: 4, trees: 2, goldfish: 3 43 | Sue 43: goldfish: 1, cats: 1, akitas: 8 44 | Sue 44: goldfish: 8, akitas: 9, vizslas: 4 45 | Sue 45: perfumes: 3, goldfish: 4, trees: 0 46 | Sue 46: trees: 7, perfumes: 1, goldfish: 8 47 | Sue 47: pomeranians: 10, cars: 7, trees: 2 48 | Sue 48: trees: 2, akitas: 1, cars: 4 49 | Sue 49: goldfish: 5, perfumes: 7, akitas: 8 50 | Sue 50: akitas: 9, vizslas: 9, trees: 2 51 | Sue 51: cars: 0, samoyeds: 0, vizslas: 8 52 | Sue 52: trees: 0, perfumes: 6, pomeranians: 4 53 | Sue 53: vizslas: 1, cats: 6, akitas: 3 54 | Sue 54: samoyeds: 8, akitas: 1, vizslas: 4 55 | Sue 55: goldfish: 10, perfumes: 2, pomeranians: 10 56 | Sue 56: trees: 9, perfumes: 3, goldfish: 5 57 | Sue 57: akitas: 3, perfumes: 0, cats: 2 58 | Sue 58: perfumes: 4, vizslas: 4, cars: 8 59 | Sue 59: goldfish: 7, children: 5, pomeranians: 8 60 | Sue 60: cars: 1, trees: 1, perfumes: 10 61 | Sue 61: trees: 4, samoyeds: 4, cars: 6 62 | Sue 62: akitas: 10, trees: 2, vizslas: 6 63 | Sue 63: goldfish: 3, perfumes: 7, vizslas: 10 64 | Sue 64: pomeranians: 5, children: 10, cars: 0 65 | Sue 65: vizslas: 10, cars: 8, perfumes: 3 66 | Sue 66: children: 5, vizslas: 4, akitas: 10 67 | Sue 67: children: 6, perfumes: 7, cars: 3 68 | Sue 68: goldfish: 8, cars: 6, children: 1 69 | Sue 69: vizslas: 5, perfumes: 3, cars: 9 70 | Sue 70: goldfish: 0, cats: 6, perfumes: 0 71 | Sue 71: trees: 2, samoyeds: 3, cars: 1 72 | Sue 72: cats: 3, akitas: 8, vizslas: 7 73 | Sue 73: akitas: 3, vizslas: 2, goldfish: 6 74 | Sue 74: pomeranians: 10, samoyeds: 9, cats: 8 75 | Sue 75: vizslas: 7, cars: 7, akitas: 10 76 | Sue 76: children: 3, cats: 6, vizslas: 3 77 | Sue 77: goldfish: 7, pomeranians: 10, trees: 0 78 | Sue 78: vizslas: 9, children: 7, trees: 10 79 | Sue 79: trees: 6, pomeranians: 8, samoyeds: 1 80 | Sue 80: vizslas: 5, children: 6, pomeranians: 5 81 | Sue 81: cars: 9, vizslas: 9, akitas: 9 82 | Sue 82: vizslas: 3, cars: 8, akitas: 1 83 | Sue 83: vizslas: 4, trees: 2, cats: 1 84 | Sue 84: children: 3, akitas: 0, vizslas: 1 85 | Sue 85: cats: 6, vizslas: 5, akitas: 2 86 | Sue 86: cars: 3, akitas: 7, goldfish: 8 87 | Sue 87: samoyeds: 8, vizslas: 3, goldfish: 8 88 | Sue 88: vizslas: 4, children: 0, cats: 7 89 | Sue 89: goldfish: 9, pomeranians: 10, samoyeds: 0 90 | Sue 90: trees: 6, akitas: 3, cars: 7 91 | Sue 91: samoyeds: 3, akitas: 7, perfumes: 10 92 | Sue 92: cars: 7, pomeranians: 10, trees: 2 93 | Sue 93: samoyeds: 1, children: 3, cars: 3 94 | Sue 94: samoyeds: 8, akitas: 7, vizslas: 0 95 | Sue 95: goldfish: 7, children: 2, cars: 6 96 | Sue 96: cars: 3, perfumes: 9, akitas: 10 97 | Sue 97: akitas: 9, cars: 10, vizslas: 10 98 | Sue 98: trees: 4, goldfish: 8, pomeranians: 7 99 | Sue 99: samoyeds: 6, pomeranians: 0, vizslas: 7 100 | Sue 100: akitas: 7, perfumes: 8, vizslas: 3 101 | Sue 101: cars: 5, perfumes: 1, trees: 0 102 | Sue 102: akitas: 6, pomeranians: 10, trees: 0 103 | Sue 103: trees: 3, perfumes: 5, cats: 9 104 | Sue 104: goldfish: 10, perfumes: 8, akitas: 0 105 | Sue 105: goldfish: 6, vizslas: 5, trees: 2 106 | Sue 106: pomeranians: 9, samoyeds: 10, perfumes: 10 107 | Sue 107: cars: 8, vizslas: 4, akitas: 2 108 | Sue 108: cats: 0, goldfish: 7, trees: 0 109 | Sue 109: cars: 3, pomeranians: 6, trees: 2 110 | Sue 110: perfumes: 4, goldfish: 5, akitas: 10 111 | Sue 111: cars: 3, perfumes: 4, pomeranians: 4 112 | Sue 112: cats: 2, goldfish: 10, akitas: 0 113 | Sue 113: cats: 10, children: 0, trees: 1 114 | Sue 114: akitas: 10, vizslas: 3, goldfish: 0 115 | Sue 115: samoyeds: 3, goldfish: 6, vizslas: 1 116 | Sue 116: cars: 3, perfumes: 5, trees: 6 117 | Sue 117: akitas: 9, samoyeds: 8, goldfish: 8 118 | Sue 118: pomeranians: 5, perfumes: 10, trees: 1 119 | Sue 119: goldfish: 6, perfumes: 3, children: 1 120 | Sue 120: trees: 1, children: 3, pomeranians: 6 121 | Sue 121: akitas: 7, cars: 10, vizslas: 9 122 | Sue 122: trees: 4, akitas: 8, samoyeds: 10 123 | Sue 123: cats: 4, cars: 8, vizslas: 9 124 | Sue 124: cars: 10, children: 1, trees: 0 125 | Sue 125: goldfish: 5, pomeranians: 5, trees: 2 126 | Sue 126: goldfish: 1, vizslas: 8, akitas: 10 127 | Sue 127: vizslas: 4, cars: 9, akitas: 1 128 | Sue 128: goldfish: 8, perfumes: 3, cars: 9 129 | Sue 129: goldfish: 9, pomeranians: 9, perfumes: 1 130 | Sue 130: trees: 1, vizslas: 9, perfumes: 3 131 | Sue 131: children: 6, trees: 8, vizslas: 8 132 | Sue 132: cars: 1, vizslas: 3, children: 7 133 | Sue 133: cars: 7, children: 1, perfumes: 6 134 | Sue 134: trees: 8, vizslas: 3, samoyeds: 2 135 | Sue 135: cats: 9, perfumes: 4, pomeranians: 7 136 | Sue 136: perfumes: 0, akitas: 8, vizslas: 6 137 | Sue 137: goldfish: 5, trees: 0, vizslas: 7 138 | Sue 138: trees: 1, perfumes: 2, cars: 10 139 | Sue 139: samoyeds: 8, goldfish: 8, trees: 0 140 | Sue 140: vizslas: 10, perfumes: 9, goldfish: 0 141 | Sue 141: perfumes: 7, cars: 9, cats: 5 142 | Sue 142: trees: 2, samoyeds: 2, cars: 0 143 | Sue 143: cars: 1, perfumes: 1, akitas: 1 144 | Sue 144: vizslas: 9, cars: 7, pomeranians: 10 145 | Sue 145: pomeranians: 2, samoyeds: 7, children: 7 146 | Sue 146: vizslas: 6, cars: 9, goldfish: 7 147 | Sue 147: trees: 2, vizslas: 1, cats: 9 148 | Sue 148: perfumes: 9, trees: 4, pomeranians: 5 149 | Sue 149: samoyeds: 8, children: 1, vizslas: 9 150 | Sue 150: cats: 3, trees: 2, vizslas: 4 151 | Sue 151: goldfish: 7, akitas: 10, trees: 3 152 | Sue 152: perfumes: 4, vizslas: 7, cars: 4 153 | Sue 153: pomeranians: 4, akitas: 0, vizslas: 3 154 | Sue 154: samoyeds: 8, trees: 2, vizslas: 10 155 | Sue 155: vizslas: 7, cats: 7, pomeranians: 5 156 | Sue 156: goldfish: 10, pomeranians: 1, vizslas: 1 157 | Sue 157: cars: 6, perfumes: 7, trees: 9 158 | Sue 158: trees: 5, samoyeds: 9, goldfish: 3 159 | Sue 159: pomeranians: 4, akitas: 6, vizslas: 8 160 | Sue 160: goldfish: 7, children: 0, cats: 0 161 | Sue 161: vizslas: 5, akitas: 0, samoyeds: 2 162 | Sue 162: akitas: 4, children: 0, vizslas: 3 163 | Sue 163: samoyeds: 2, perfumes: 0, goldfish: 9 164 | Sue 164: cars: 9, vizslas: 8, akitas: 6 165 | Sue 165: samoyeds: 9, vizslas: 9, perfumes: 5 166 | Sue 166: cars: 5, pomeranians: 4, samoyeds: 8 167 | Sue 167: cars: 10, perfumes: 3, samoyeds: 6 168 | Sue 168: pomeranians: 8, goldfish: 9, trees: 9 169 | Sue 169: vizslas: 7, akitas: 3, samoyeds: 4 170 | Sue 170: cats: 2, goldfish: 0, vizslas: 4 171 | Sue 171: perfumes: 3, goldfish: 10, cats: 3 172 | Sue 172: goldfish: 7, akitas: 6, cars: 0 173 | Sue 173: cars: 9, goldfish: 7, akitas: 5 174 | Sue 174: goldfish: 6, cats: 0, vizslas: 8 175 | Sue 175: perfumes: 7, cats: 10, cars: 10 176 | Sue 176: samoyeds: 9, vizslas: 4, pomeranians: 10 177 | Sue 177: perfumes: 0, trees: 0, cars: 10 178 | Sue 178: vizslas: 6, children: 7, samoyeds: 1 179 | Sue 179: vizslas: 8, children: 6, trees: 0 180 | Sue 180: cars: 1, vizslas: 6, trees: 1 181 | Sue 181: vizslas: 10, perfumes: 3, cars: 1 182 | Sue 182: trees: 8, samoyeds: 9, cars: 7 183 | Sue 183: cars: 6, vizslas: 2, perfumes: 7 184 | Sue 184: trees: 5, samoyeds: 9, akitas: 0 185 | Sue 185: cars: 8, goldfish: 8, trees: 4 186 | Sue 186: samoyeds: 6, goldfish: 1, trees: 2 187 | Sue 187: perfumes: 1, trees: 2, akitas: 7 188 | Sue 188: samoyeds: 5, cars: 6, perfumes: 2 189 | Sue 189: samoyeds: 8, goldfish: 3, perfumes: 5 190 | Sue 190: akitas: 2, cats: 1, samoyeds: 1 191 | Sue 191: trees: 5, akitas: 1, goldfish: 7 192 | Sue 192: vizslas: 3, trees: 0, perfumes: 4 193 | Sue 193: cars: 3, perfumes: 4, akitas: 3 194 | Sue 194: perfumes: 4, vizslas: 8, children: 4 195 | Sue 195: vizslas: 1, samoyeds: 3, cars: 6 196 | Sue 196: cars: 5, perfumes: 6, vizslas: 2 197 | Sue 197: vizslas: 8, akitas: 8, cats: 6 198 | Sue 198: cars: 9, akitas: 2, pomeranians: 7 199 | Sue 199: cats: 9, akitas: 6, cars: 10 200 | Sue 200: vizslas: 10, pomeranians: 2, goldfish: 9 201 | Sue 201: vizslas: 9, samoyeds: 4, akitas: 3 202 | Sue 202: akitas: 5, cats: 2, vizslas: 0 203 | Sue 203: perfumes: 1, children: 3, akitas: 10 204 | Sue 204: trees: 4, vizslas: 7, akitas: 9 205 | Sue 205: trees: 8, perfumes: 9, cars: 1 206 | Sue 206: goldfish: 6, trees: 5, cars: 8 207 | Sue 207: akitas: 3, vizslas: 8, trees: 8 208 | Sue 208: vizslas: 4, perfumes: 7, akitas: 10 209 | Sue 209: cars: 9, perfumes: 7, goldfish: 9 210 | Sue 210: vizslas: 2, cats: 2, akitas: 10 211 | Sue 211: akitas: 1, trees: 3, cars: 2 212 | Sue 212: goldfish: 5, trees: 0, vizslas: 7 213 | Sue 213: akitas: 3, perfumes: 1, vizslas: 5 214 | Sue 214: perfumes: 3, pomeranians: 6, cars: 0 215 | Sue 215: goldfish: 1, cats: 9, cars: 3 216 | Sue 216: goldfish: 9, pomeranians: 6, samoyeds: 0 217 | Sue 217: cars: 6, trees: 2, perfumes: 2 218 | Sue 218: vizslas: 3, goldfish: 8, akitas: 5 219 | Sue 219: cats: 9, perfumes: 7, cars: 5 220 | Sue 220: pomeranians: 5, vizslas: 4, cats: 5 221 | Sue 221: trees: 0, akitas: 7, goldfish: 10 222 | Sue 222: akitas: 2, cars: 3, vizslas: 5 223 | Sue 223: goldfish: 3, perfumes: 7, akitas: 4 224 | Sue 224: samoyeds: 2, cars: 4, vizslas: 7 225 | Sue 225: trees: 5, cars: 0, perfumes: 0 226 | Sue 226: trees: 2, goldfish: 10, perfumes: 6 227 | Sue 227: cars: 8, trees: 9, akitas: 6 228 | Sue 228: goldfish: 10, trees: 10, perfumes: 0 229 | Sue 229: children: 7, samoyeds: 4, goldfish: 6 230 | Sue 230: vizslas: 9, perfumes: 1, children: 10 231 | Sue 231: vizslas: 8, trees: 5, akitas: 9 232 | Sue 232: akitas: 5, goldfish: 9, trees: 1 233 | Sue 233: vizslas: 3, trees: 2, children: 9 234 | Sue 234: samoyeds: 8, perfumes: 0, cats: 0 235 | Sue 235: perfumes: 4, vizslas: 3, akitas: 5 236 | Sue 236: pomeranians: 5, vizslas: 3, akitas: 9 237 | Sue 237: cats: 1, trees: 7, vizslas: 5 238 | Sue 238: children: 5, cats: 4, samoyeds: 5 239 | Sue 239: trees: 3, akitas: 2, goldfish: 6 240 | Sue 240: goldfish: 9, trees: 1, perfumes: 1 241 | Sue 241: cars: 2, pomeranians: 1, samoyeds: 2 242 | Sue 242: akitas: 2, trees: 3, cars: 4 243 | Sue 243: vizslas: 6, akitas: 2, samoyeds: 7 244 | Sue 244: trees: 0, perfumes: 5, cars: 7 245 | Sue 245: goldfish: 10, perfumes: 5, vizslas: 8 246 | Sue 246: akitas: 0, perfumes: 0, cars: 1 247 | Sue 247: samoyeds: 8, goldfish: 0, cars: 6 248 | Sue 248: perfumes: 0, children: 10, trees: 10 249 | Sue 249: perfumes: 6, akitas: 5, cats: 5 250 | Sue 250: vizslas: 7, akitas: 4, cats: 5 251 | Sue 251: samoyeds: 4, akitas: 1, trees: 8 252 | Sue 252: perfumes: 8, pomeranians: 5, cars: 1 253 | Sue 253: akitas: 10, trees: 4, cats: 3 254 | Sue 254: perfumes: 2, cats: 2, goldfish: 9 255 | Sue 255: cars: 4, trees: 1, akitas: 4 256 | Sue 256: samoyeds: 9, goldfish: 0, akitas: 9 257 | Sue 257: vizslas: 9, perfumes: 2, goldfish: 2 258 | Sue 258: perfumes: 1, cars: 9, samoyeds: 1 259 | Sue 259: trees: 0, goldfish: 0, samoyeds: 3 260 | Sue 260: perfumes: 7, cars: 1, goldfish: 0 261 | Sue 261: cars: 0, trees: 5, goldfish: 6 262 | Sue 262: akitas: 7, vizslas: 3, pomeranians: 5 263 | Sue 263: trees: 1, vizslas: 3, goldfish: 3 264 | Sue 264: akitas: 7, vizslas: 4, children: 0 265 | Sue 265: samoyeds: 5, trees: 0, akitas: 4 266 | Sue 266: perfumes: 9, goldfish: 9, cars: 8 267 | Sue 267: cars: 7, perfumes: 10, pomeranians: 8 268 | Sue 268: cars: 0, akitas: 7, perfumes: 4 269 | Sue 269: pomeranians: 0, cars: 9, perfumes: 10 270 | Sue 270: samoyeds: 10, perfumes: 10, cars: 9 271 | Sue 271: akitas: 2, vizslas: 8, cats: 5 272 | Sue 272: akitas: 3, children: 9, samoyeds: 10 273 | Sue 273: perfumes: 2, cars: 10, goldfish: 8 274 | Sue 274: cars: 3, children: 10, perfumes: 10 275 | Sue 275: cats: 9, akitas: 5, trees: 0 276 | Sue 276: akitas: 6, children: 2, vizslas: 1 277 | Sue 277: pomeranians: 6, trees: 10, samoyeds: 3 278 | Sue 278: cars: 7, perfumes: 10, trees: 1 279 | Sue 279: cars: 6, pomeranians: 8, trees: 2 280 | Sue 280: pomeranians: 9, cats: 0, perfumes: 7 281 | Sue 281: vizslas: 10, goldfish: 9, pomeranians: 5 282 | Sue 282: perfumes: 4, samoyeds: 7, cars: 9 283 | Sue 283: cars: 9, vizslas: 6, trees: 5 284 | Sue 284: cars: 7, trees: 1, vizslas: 4 285 | Sue 285: samoyeds: 4, goldfish: 10, cats: 4 286 | Sue 286: samoyeds: 0, akitas: 4, children: 5 287 | Sue 287: trees: 1, perfumes: 3, goldfish: 10 288 | Sue 288: pomeranians: 10, akitas: 3, cars: 2 289 | Sue 289: trees: 7, pomeranians: 4, goldfish: 10 290 | Sue 290: samoyeds: 10, perfumes: 0, cars: 9 291 | Sue 291: akitas: 0, pomeranians: 7, vizslas: 4 292 | Sue 292: cats: 2, vizslas: 8, goldfish: 5 293 | Sue 293: vizslas: 6, pomeranians: 9, perfumes: 0 294 | Sue 294: akitas: 6, cars: 7, vizslas: 5 295 | Sue 295: goldfish: 0, akitas: 9, cats: 0 296 | Sue 296: goldfish: 1, trees: 0, cars: 6 297 | Sue 297: perfumes: 6, cats: 8, pomeranians: 6 298 | Sue 298: cats: 0, goldfish: 6, perfumes: 2 299 | Sue 299: cars: 4, akitas: 1, samoyeds: 10 300 | Sue 300: goldfish: 9, samoyeds: 6, cats: 5 301 | Sue 301: cars: 0, vizslas: 7, trees: 0 302 | Sue 302: goldfish: 9, samoyeds: 1, children: 6 303 | Sue 303: cars: 6, perfumes: 7, samoyeds: 8 304 | Sue 304: trees: 8, goldfish: 9, children: 9 305 | Sue 305: perfumes: 0, cars: 5, goldfish: 4 306 | Sue 306: cats: 3, cars: 7, vizslas: 7 307 | Sue 307: pomeranians: 4, perfumes: 6, cars: 2 308 | Sue 308: cars: 9, akitas: 6, goldfish: 4 309 | Sue 309: pomeranians: 2, vizslas: 10, goldfish: 10 310 | Sue 310: children: 0, cats: 4, akitas: 7 311 | Sue 311: children: 10, akitas: 8, vizslas: 2 312 | Sue 312: children: 5, cars: 0, vizslas: 4 313 | Sue 313: perfumes: 10, trees: 3, pomeranians: 9 314 | Sue 314: samoyeds: 3, goldfish: 2, trees: 9 315 | Sue 315: cars: 2, cats: 5, pomeranians: 10 316 | Sue 316: cats: 6, pomeranians: 6, children: 9 317 | Sue 317: cats: 2, vizslas: 3, perfumes: 1 318 | Sue 318: akitas: 1, perfumes: 3, vizslas: 10 319 | Sue 319: cars: 7, perfumes: 0, trees: 0 320 | Sue 320: goldfish: 6, samoyeds: 6, pomeranians: 4 321 | Sue 321: trees: 2, goldfish: 6, children: 0 322 | Sue 322: goldfish: 0, trees: 2, akitas: 8 323 | Sue 323: pomeranians: 2, samoyeds: 9, vizslas: 1 324 | Sue 324: trees: 4, goldfish: 6, pomeranians: 6 325 | Sue 325: trees: 2, pomeranians: 3, goldfish: 1 326 | Sue 326: perfumes: 4, goldfish: 6, trees: 5 327 | Sue 327: akitas: 3, cars: 8, cats: 2 328 | Sue 328: cats: 6, vizslas: 0, akitas: 2 329 | Sue 329: perfumes: 3, goldfish: 10, akitas: 3 330 | Sue 330: goldfish: 3, vizslas: 1, akitas: 6 331 | Sue 331: perfumes: 4, trees: 1, goldfish: 5 332 | Sue 332: goldfish: 7, vizslas: 9, akitas: 1 333 | Sue 333: children: 8, cars: 8, trees: 4 334 | Sue 334: cars: 1, vizslas: 6, trees: 0 335 | Sue 335: goldfish: 2, cars: 2, akitas: 1 336 | Sue 336: goldfish: 5, akitas: 5, trees: 9 337 | Sue 337: cars: 5, vizslas: 6, goldfish: 6 338 | Sue 338: cats: 9, akitas: 3, goldfish: 9 339 | Sue 339: akitas: 3, cats: 2, children: 7 340 | Sue 340: goldfish: 0, pomeranians: 8, perfumes: 9 341 | Sue 341: trees: 0, pomeranians: 1, goldfish: 5 342 | Sue 342: goldfish: 10, trees: 3, vizslas: 4 343 | Sue 343: cats: 3, samoyeds: 1, children: 6 344 | Sue 344: perfumes: 3, children: 4, samoyeds: 2 345 | Sue 345: children: 6, trees: 2, goldfish: 1 346 | Sue 346: trees: 2, pomeranians: 3, goldfish: 5 347 | Sue 347: akitas: 10, vizslas: 7, trees: 1 348 | Sue 348: perfumes: 4, akitas: 2, vizslas: 7 349 | Sue 349: perfumes: 8, goldfish: 3, vizslas: 5 350 | Sue 350: trees: 4, pomeranians: 5, akitas: 10 351 | Sue 351: perfumes: 5, cars: 9, trees: 0 352 | Sue 352: akitas: 6, children: 8, trees: 10 353 | Sue 353: samoyeds: 7, akitas: 6, vizslas: 4 354 | Sue 354: children: 9, goldfish: 7, perfumes: 5 355 | Sue 355: trees: 1, perfumes: 4, cars: 1 356 | Sue 356: samoyeds: 1, perfumes: 4, pomeranians: 8 357 | Sue 357: trees: 7, goldfish: 10, akitas: 0 358 | Sue 358: akitas: 1, vizslas: 6, cars: 7 359 | Sue 359: vizslas: 3, goldfish: 8, trees: 4 360 | Sue 360: akitas: 10, vizslas: 2, trees: 3 361 | Sue 361: samoyeds: 6, pomeranians: 1, perfumes: 0 362 | Sue 362: samoyeds: 3, cars: 1, trees: 0 363 | Sue 363: vizslas: 0, pomeranians: 9, akitas: 4 364 | Sue 364: perfumes: 9, pomeranians: 8, vizslas: 9 365 | Sue 365: vizslas: 7, cars: 4, perfumes: 10 366 | Sue 366: cars: 0, samoyeds: 5, goldfish: 10 367 | Sue 367: children: 4, vizslas: 5, akitas: 4 368 | Sue 368: samoyeds: 9, perfumes: 4, vizslas: 6 369 | Sue 369: perfumes: 5, cars: 4, samoyeds: 5 370 | Sue 370: akitas: 3, vizslas: 2, perfumes: 1 371 | Sue 371: cars: 8, cats: 7, children: 5 372 | Sue 372: vizslas: 9, perfumes: 2, akitas: 10 373 | Sue 373: trees: 10, pomeranians: 9, goldfish: 3 374 | Sue 374: children: 4, cars: 10, perfumes: 2 375 | Sue 375: children: 7, samoyeds: 5, cats: 0 376 | Sue 376: akitas: 10, samoyeds: 5, vizslas: 5 377 | Sue 377: goldfish: 8, trees: 3, perfumes: 3 378 | Sue 378: goldfish: 10, vizslas: 0, perfumes: 2 379 | Sue 379: trees: 1, vizslas: 7, pomeranians: 4 380 | Sue 380: samoyeds: 8, vizslas: 3, trees: 2 381 | Sue 381: goldfish: 2, perfumes: 5, samoyeds: 9 382 | Sue 382: cats: 3, vizslas: 10, akitas: 5 383 | Sue 383: cars: 7, goldfish: 5, akitas: 8 384 | Sue 384: children: 6, goldfish: 10, trees: 1 385 | Sue 385: cats: 2, akitas: 6, samoyeds: 7 386 | Sue 386: cars: 10, children: 4, goldfish: 2 387 | Sue 387: cats: 0, perfumes: 5, akitas: 9 388 | Sue 388: pomeranians: 7, akitas: 0, samoyeds: 9 389 | Sue 389: trees: 0, akitas: 9, vizslas: 8 390 | Sue 390: cars: 0, trees: 10, perfumes: 9 391 | Sue 391: cats: 9, goldfish: 10, perfumes: 10 392 | Sue 392: cars: 3, vizslas: 6, cats: 3 393 | Sue 393: vizslas: 10, perfumes: 4, goldfish: 5 394 | Sue 394: perfumes: 4, akitas: 10, trees: 2 395 | Sue 395: pomeranians: 5, cars: 4, perfumes: 3 396 | Sue 396: pomeranians: 9, vizslas: 5, akitas: 2 397 | Sue 397: cars: 10, goldfish: 8, trees: 2 398 | Sue 398: perfumes: 7, children: 9, goldfish: 9 399 | Sue 399: akitas: 6, cats: 2, goldfish: 7 400 | Sue 400: goldfish: 9, perfumes: 0, cars: 2 401 | Sue 401: children: 4, vizslas: 0, trees: 2 402 | Sue 402: akitas: 4, cars: 8, pomeranians: 4 403 | Sue 403: vizslas: 8, perfumes: 7, goldfish: 1 404 | Sue 404: goldfish: 10, samoyeds: 7, vizslas: 3 405 | Sue 405: akitas: 1, vizslas: 6, perfumes: 6 406 | Sue 406: pomeranians: 8, goldfish: 6, cats: 3 407 | Sue 407: goldfish: 2, vizslas: 4, akitas: 7 408 | Sue 408: cars: 10, perfumes: 10, vizslas: 3 409 | Sue 409: vizslas: 7, pomeranians: 4, perfumes: 4 410 | Sue 410: goldfish: 4, vizslas: 7, trees: 5 411 | Sue 411: cars: 8, trees: 0, goldfish: 4 412 | Sue 412: cars: 8, perfumes: 5, vizslas: 4 413 | Sue 413: vizslas: 3, akitas: 7, samoyeds: 6 414 | Sue 414: trees: 0, perfumes: 6, cars: 10 415 | Sue 415: pomeranians: 4, trees: 1, perfumes: 6 416 | Sue 416: cars: 10, perfumes: 6, akitas: 2 417 | Sue 417: perfumes: 6, samoyeds: 0, akitas: 0 418 | Sue 418: children: 1, perfumes: 9, vizslas: 3 419 | Sue 419: goldfish: 9, samoyeds: 3, perfumes: 8 420 | Sue 420: goldfish: 4, cars: 10, vizslas: 7 421 | Sue 421: samoyeds: 7, vizslas: 7, cats: 2 422 | Sue 422: trees: 1, goldfish: 8, perfumes: 0 423 | Sue 423: cars: 3, perfumes: 2, trees: 3 424 | Sue 424: samoyeds: 6, vizslas: 0, akitas: 6 425 | Sue 425: trees: 3, akitas: 7, goldfish: 1 426 | Sue 426: cars: 9, trees: 1, perfumes: 0 427 | Sue 427: pomeranians: 0, children: 5, perfumes: 8 428 | Sue 428: cars: 0, perfumes: 6, children: 4 429 | Sue 429: akitas: 7, pomeranians: 9, cats: 6 430 | Sue 430: cats: 6, trees: 1, cars: 0 431 | Sue 431: children: 8, akitas: 5, perfumes: 9 432 | Sue 432: perfumes: 5, akitas: 10, trees: 9 433 | Sue 433: akitas: 4, perfumes: 10, vizslas: 7 434 | Sue 434: trees: 3, children: 10, samoyeds: 4 435 | Sue 435: vizslas: 5, goldfish: 2, akitas: 2 436 | Sue 436: samoyeds: 3, trees: 2, cars: 6 437 | Sue 437: children: 9, akitas: 0, pomeranians: 3 438 | Sue 438: perfumes: 10, akitas: 2, cars: 7 439 | Sue 439: perfumes: 10, samoyeds: 6, akitas: 10 440 | Sue 440: vizslas: 10, trees: 2, akitas: 8 441 | Sue 441: perfumes: 8, akitas: 2, pomeranians: 7 442 | Sue 442: cars: 8, trees: 3, goldfish: 6 443 | Sue 443: cars: 1, goldfish: 5, vizslas: 5 444 | Sue 444: vizslas: 2, akitas: 10, samoyeds: 4 445 | Sue 445: vizslas: 2, akitas: 10, perfumes: 9 446 | Sue 446: akitas: 3, vizslas: 8, goldfish: 1 447 | Sue 447: vizslas: 7, pomeranians: 5, trees: 10 448 | Sue 448: cats: 6, perfumes: 10, children: 6 449 | Sue 449: trees: 2, cars: 5, goldfish: 8 450 | Sue 450: trees: 0, goldfish: 6, samoyeds: 3 451 | Sue 451: perfumes: 0, cars: 8, trees: 1 452 | Sue 452: akitas: 4, trees: 8, perfumes: 9 453 | Sue 453: goldfish: 1, perfumes: 7, akitas: 6 454 | Sue 454: vizslas: 3, cars: 1, perfumes: 6 455 | Sue 455: trees: 1, akitas: 7, goldfish: 10 456 | Sue 456: samoyeds: 4, vizslas: 2, cars: 9 457 | Sue 457: perfumes: 10, children: 1, trees: 8 458 | Sue 458: perfumes: 0, vizslas: 9, cars: 8 459 | Sue 459: cats: 0, children: 7, trees: 3 460 | Sue 460: vizslas: 4, cats: 6, perfumes: 2 461 | Sue 461: trees: 3, children: 5, cars: 8 462 | Sue 462: goldfish: 7, vizslas: 7, children: 5 463 | Sue 463: cars: 5, akitas: 3, goldfish: 5 464 | Sue 464: vizslas: 0, pomeranians: 5, cars: 0 465 | Sue 465: goldfish: 4, akitas: 0, cats: 5 466 | Sue 466: cars: 5, trees: 1, goldfish: 6 467 | Sue 467: perfumes: 10, trees: 8, cars: 1 468 | Sue 468: perfumes: 4, akitas: 3, cars: 0 469 | Sue 469: vizslas: 3, cars: 7, pomeranians: 1 470 | Sue 470: perfumes: 1, vizslas: 7, akitas: 8 471 | Sue 471: goldfish: 10, samoyeds: 10, pomeranians: 5 472 | Sue 472: goldfish: 6, trees: 0, perfumes: 0 473 | Sue 473: goldfish: 5, vizslas: 0, children: 5 474 | Sue 474: cars: 3, vizslas: 7, perfumes: 10 475 | Sue 475: vizslas: 5, trees: 9, goldfish: 8 476 | Sue 476: akitas: 2, goldfish: 6, children: 7 477 | Sue 477: samoyeds: 0, perfumes: 1, pomeranians: 5 478 | Sue 478: trees: 2, goldfish: 9, vizslas: 0 479 | Sue 479: perfumes: 1, cars: 6, goldfish: 9 480 | Sue 480: pomeranians: 3, perfumes: 5, trees: 9 481 | Sue 481: cats: 3, akitas: 0, vizslas: 8 482 | Sue 482: pomeranians: 10, akitas: 8, trees: 5 483 | Sue 483: goldfish: 6, akitas: 10, perfumes: 2 484 | Sue 484: cats: 0, goldfish: 0, children: 9 485 | Sue 485: children: 4, akitas: 10, vizslas: 8 486 | Sue 486: vizslas: 3, goldfish: 9, children: 10 487 | Sue 487: children: 8, cats: 6, vizslas: 10 488 | Sue 488: cars: 7, akitas: 10, samoyeds: 5 489 | Sue 489: vizslas: 9, akitas: 6, trees: 2 490 | Sue 490: vizslas: 5, akitas: 1, children: 5 491 | Sue 491: vizslas: 8, goldfish: 3, perfumes: 6 492 | Sue 492: trees: 3, samoyeds: 1, pomeranians: 6 493 | Sue 493: akitas: 1, vizslas: 5, cars: 8 494 | Sue 494: akitas: 4, cars: 4, vizslas: 9 495 | Sue 495: vizslas: 1, akitas: 2, cats: 2 496 | Sue 496: trees: 7, vizslas: 5, akitas: 6 497 | Sue 497: akitas: 8, trees: 2, perfumes: 6 498 | Sue 498: akitas: 1, trees: 1, samoyeds: 4 499 | Sue 499: cars: 0, akitas: 5, vizslas: 3 500 | Sue 500: cats: 2, goldfish: 9, children: 8 501 | -------------------------------------------------------------------------------- /input17.txt: -------------------------------------------------------------------------------- 1 | 33 2 | 14 3 | 18 4 | 20 5 | 45 6 | 35 7 | 16 8 | 35 9 | 1 10 | 13 11 | 18 12 | 13 13 | 50 14 | 44 15 | 48 16 | 6 17 | 24 18 | 41 19 | 30 20 | 42 21 | -------------------------------------------------------------------------------- /input18.txt: -------------------------------------------------------------------------------- 1 | #..####.##..#...#..#...#...###.#.#.#..#....#.##..#...##...#..#.....##..#####....#.##..##....##.#.... 2 | .#..#..#..#.###...##..#.##.....#...#..##....#####.##............####.#..######..#.#.##.#...#..#...## 3 | #.....##.##.##.#..##.#..###...#.#.#..##..###.####.####.#.####.#...##.#..###.........#.###...#....### 4 | #.###..#######..##..#.....##.#.#.###.#.##..#.##..##.##.#.##...###.#...#.#####.#.##..#.#####..#.##### 5 | #.##.##.###.##..###.#.##.##...##.#.#..##..###.########.#.####..####...#####...#..#...##....##.##.##. 6 | ..#.#.#.#..#.#.###....###...#...#.##..####.###.....#.####.###.###.#......#.#.###..#..#.#....#.#####. 7 | ...#.###.#....#.###...#.#.#...#...#.#####....#....#...#####..#..#.#..######..#.##.#.##.#..###.#...## 8 | .###...#...#.#..#.#.####.#...#.....##...###.#....#..##.###....#.##....###..#.#####...###.#.##.####.. 9 | #.#....##.#.....#####.#.##..#######.#.####..###.##.#####.##.#...###...#.#...###..#...#.#.###.###.### 10 | ...##.##.....##..#.##...#.#...#...#.#####.#...#.#.#.#####.##.#...#.#..##.##..#...#....####..###.###. 11 | #..#....######...#...###.#....#####....#.#.#....#....#.#######.#####..#....#....#.##..#.##.###..#... 12 | #####.#.######.#.#####.#..##..##..####..#....#...#######....##..##.#..###..###.###..###...#...###### 13 | #...##..##...###....##..##.##..#.#.#.#....##.#.......###..###..###...###..##.##.##.#.#.#..#.#..#..#. 14 | ..###....##.###..#.#..########...###...##..#######....##..###..#####.##.#....###..##.##.##.#...##.#. 15 | ###..#.#..#.#.##.##...##.....#..###.#..##.##.#....##.#.######..##..#.#.##.###...#..####...#.#..#.### 16 | .######....#..##..#.####.##..#.#..#.#..#....#..##.#..#.#...####..#....#.####.#.###.#...####.#...#.#. 17 | #.######.##..###.###..#..###.#...#..#...#...###.##....#.#......#...#.##.#.###..#.#####.#.#..###..#.# 18 | ...#..#...####..###.########.....###.###.#..##.##....######..#..#.....#.##.##.#..##..#..##...#..#..# 19 | #..#..##..#.#.########.##.#.####..#.#####.#.###.##....###..##..#.#.###..#.##..##.##.####...######.## 20 | .######.###....#...##...#..#....##..#.#...###.######.##...#....##.##.#.#.##..#...###.###.#....#..##. 21 | ####.#.##..##.##.###...#.###.##..##....###..####.##..#.#.##..###.#..##...####...#..####.#.#..##...#. 22 | .#.#..#.....##...#..#...#.#...#.#.##..#....#..#......#####.#######....#.#..#..###..##.#.########..## 23 | .##.#..#..##..#..####.#...####...#...#..##.#..###.#..######..#.#...###.##...#..#####..##.#..##.#.##. 24 | .###..##.##.##....###.###..#.#...##.#.#...#.#######.####..#..###.#######.#...#.#...#.##...#..####..# 25 | ##.########..#..#....#.###..##.##.#.##.#..#......####..##.##.#..####..#####..#.....#####.###..#.#.#. 26 | .#..####..##.#.#..#####.##..#..#.#....#.#####.#####...######........##.##..##.#.#.###..#.#.#.#..##.# 27 | .##..##..#.######..###....#.#.###.#........#..###..#.########.....#.##...#.....#..#...##...#..#.###. 28 | ##.##.#..####....####.#######.....#.#.#...#.######.#.....####.####...###..####.##.##....###..#..#... 29 | #.#..####...#......#...###...##....##.#######..#.###.#...###.##.##...####..#.####..#......##..#####. 30 | .#.#...##...#....#.####.##.....#....#.#.#######..###.#.....#.....####...##...#.#.##.####..##.###.#.# 31 | ####.#.#.####...#...####.#.....#.#######.#.......####......###..###.#...######..#.##.#.##..#..##..## 32 | ..##.###..#..####..####.......######.##..#.....##.##...##.##......#.###..###...#.##.#####.#.######.# 33 | .###..####.###..#..#.......#.##...##...##.######.....#..####.#......#.#...#...#...###...#.#.##..#### 34 | .####....##.##.#.....##.###.####.#.......#.......#.#..#.#.#.....###.#.#####.#..#.#.#####.#####.###.# 35 | .##.#.###.#####..#..#....###.#.#.#..#..###..##..####..##.###....#..####.####.#..###.#..######.###### 36 | ####.#.....##..###....#.....#.##.#.##..##..########.#####..###.####....##.....######.#.#.##.......#. 37 | #.#.##.....#.....##.###.#..#.##.##....#..##....##.#.###.##.#..#..##.##.###.#..##.###...##..###.##### 38 | #.###.#.#.#.#.#.#.#...#..#.###..####.##...#..####.###....#..#..##.#....####..##.##....#.#.##.##....# 39 | ...######....#..####...#.#..#.#.#..#.##.#.#.......#..#......##..#...#..#..##...##.#...#.#.#...##.##. 40 | .#####..#...####....#..###..##....#####..###.#.#...###..###.###..##...#......#...#...#.#.#...#.##..# 41 | ......#####.#...#.#.#.##..#.###..##..#.#...###..###....##..#####..#######.#..#.###....###...##.#..#. 42 | ..##.########.##..#....##.#...##.##.#.#..#.##..#.#.#.##....#.#.#.#.##....##....#....#####.##..#.##.# 43 | ####...#....##.#.###......##.##.#..##...#..#####..#.#....##..#####...#.#.##...#.####.####..##.###### 44 | .##.###.##.#...#.#....###.#######...##...##..#..##.###.#.####..#..###......#.#.##.#.#....#..##...#.. 45 | .#.###.#.###.###.#.##.#..#......####.##...#..##.#..####.....#...#.###.##.##.#..#.##..#.###......#..# 46 | ...##.####......#.#.#..###..#....###....#.##.#####..#..#..#...#.#.###...#.#.#.##....###.####..###.#. 47 | ##..#.#.#.#....####...#.##.###..####....#..#####.######..#.##.##..#####.#.....#.#...##.#.##.##.#.#.. 48 | #..##.#.#.#.###.#.#.###...#.#...##..#..#.#.#.##..###...#..##.#..#.#.#..#.....#.######.#.###..###.#.. 49 | ....#.#.##.###.##...#.##.#....#..##.#..##...#...#.##.####...##..####.#.........#..##..#...#...##.#.. 50 | .##.......##...###.##.#.##.###.##.#..#..#..####...#...#....#####...###..##..#..#..##...#....#..##### 51 | ..####..#...#...#..###....##.#.#####..#..#.....#......#...#.......##....####...##....##.##.#.#####.# 52 | ##.#.#.#..##..##..#.####.##.##.###.#...###.#....#.....#.###...#######..###.####.###.####.##...##.#.. 53 | ..#.#...##.#....#..#..##.####.....#.#.#...#..#..###.#..###.#####.#.#####.#.#.#.#.###.##.###..#....## 54 | .###.#...#....###..#...####....####..#.##..#..##.###..#.#.#.#..#...###.#.#...#......#...#.##.##.#... 55 | ..####.####.##.#.##....#...##....#..#....#..###..#...#..###.#####.....#####..##.#.#.#.#.#.##.####... 56 | ...##.#.##.####..##.###..#.#.#.#.#.#.#..###...#.##..#.####.##...#.#.##......###..#...###....#.#.###. 57 | ##...##..#.#.##..#.#.#....#.####.......#.#.#######.#..#....#.###.#...###.##....###.#.#..#.#.##.####. 58 | ...##.......######.....##....#...#..#.##.###.#..#.##.###.#.###.#.#.#...#.#...##.##.##..#.##########. 59 | ###..#....#.#.....#....###.#...##.......##.#.#..#.#...########......###..##.#..#..####.##..####...#. 60 | ......##.###.#.###.....#..#...#.#......##....#....#........#..#...##.##.....#...##.##.........##.... 61 | .##.##.#.#...#....######..##....##..##.#.#.##.#.##..##...#..###......##......#.#....#.#.#.......###. 62 | .......#.##..##.#...#.##..#..#####.#..#.######.........###.#####.####.#...##...........##...##..#### 63 | #......#.#..#...#...##..#.#.###.##.##.#.#..#.###.##.#..###..#.###..#...###.##..###..#...#..###...#.. 64 | ####.##..#####..####.#...#..#..###..##.#.#...#...#...#.##.####.##.###....###...#.#.#..####.######.## 65 | .....#..####...#.#.#.####..####..##.###......#.....########.#...#.#..#..#...#.###..##.#####..###.### 66 | .#######.#.##..###.#...###.#####............##.###...#.##.#.##..##.#.#..#.######..######..#..#..#### 67 | ...##..#.####...#..#.#.##.#....#.####..#..###.###..#.#...#....##.##.#......##..##..#.#.#.###..#..#.. 68 | ........#...#.##.#.#..#....####....#.##...###..####...###.#.#..######..###..##.#####.###.###.#.#...# 69 | ##......##.#..###.####.##.#.###.#.......#.##..####..#.###.##..##..##...##...#.###...#.#..#..#.#####. 70 | ##..#.#.....##.####.#..##.#.##.#.#...#...#.#...####.#.#.##...##....##.###..###.####.#...#.###..##### 71 | .#####.####.####.####.#.##.##......###....###.####...###...#...#..#.##.#.#####.###..##.#..###...##.. 72 | .#...#..##...##...#....#.#.#..##..#.##..#.###.#.###..###.#.#.###.#....#######.####.##..#..#...####.. 73 | ..##.##..#.##..#.#.###..#.##.########...####.#.###.##..#..###.###...##..##.#..#.######.##.#....###.# 74 | ##.#####.###.##.#.##.##.##.###..##..##..#.#.#.#.####..#......#.#.#.#.#.#.##...#####.####...#.#...#.# 75 | .#..###..##.#####.#.##.#..##...##..##...#####.#.####..#...##.....######.#.#...##.#..#######.###.###. 76 | #.#..##.#.#####.#.#.....###.###.#..##.#####....#.###.##.##.#.#..##..#.#....#######.###.#.#.....#.### 77 | ....###...#.###.####....###.....##....#####.##.###.###.##.##.##.#..###..######...####.#.#..####..#.. 78 | ###.....#..####..#.####..#..#...##.##..##.######.####.....#...##....#..#.##.#####..###.##.#.####...# 79 | .##.##.#...#..####...##.##.###...#...#..#.#.#####.....####...#.#.#..#.####...####.#...###.#......### 80 | ###.##....#.#.#...#.###....####..##...##.##.##.#..#...####..#..#..##...#####.####.####...##.#..###.# 81 | ..####.....##..###.#.#.###.########..#...#.##..#.#.#.......#.##.#..#...####.##.#..#.######..#.#...#. 82 | #.#.##.#.#.##.#....##......##......#######.#..#.##...##..#.#.###...#.#..#..###...#..###.....##.....# 83 | ..#.##.#.##.#.##..##.....#.#..#.#..#...##..#..#.#....###.#####....####.####..#####.##.###...#..###.# 84 | #....#.###..#..########.###..#.#.#.##...##.#..##.###..#..#..#.#.##..###...###.#.##..#.##.#..#.#.#### 85 | #.......#######......#...#...##.##...###.#....##.#..#....####.#.##.###...#.#####...##.###........##. 86 | .##.####.....###.##......####.###.########..#.####..#.##.#.####.....#...#.##....#######.##..#......# 87 | #.#.##.##....##..##.#.###..#.##.#..#..#.#..##.....###..###.##.##.####.##.#.#.##...####..#.#..##.#.#. 88 | ...##.#.#.#...###.#.......#.#.....#.#...##....##.##.##.####...#.#..#..#..#.#.##.#..#.#.#....###..#.# 89 | ....#.#.###.#####.##..###..##..#...#.##.#......##.####.#..####.#.##..####.#.#...##..#####..##.#.#... 90 | ..###.#.##..#....#..#.#.....##.#####..##....#.#...#.##..##.#.#..#...##.##..##..##....#...#..#..#..## 91 | ##.#.##.#...#.###.##.##.##.##..##.##...#..##.#..#######.#..#...#.#.##..#....##.#..####.###........#. 92 | .##.#..#.....#####..##.#.#.#.#..###.#######.###.###....##....#.#.#.###....###.#..#.#....#.#..###...# 93 | ...###.#.#.###..#...#..###.######..##.#.#..#...####.#####.##..#..###...#..#..#..###..##.#.#...#.###. 94 | #......#.#..#..##.##.#.##.#.###.#.##.#.#..#....#.##..#..##..##.#.#.#....##.###.###.####.#.#####...## 95 | ...#.##..#.######.......#.#.###.....#####....##.#.#.###........#.#.###.#.#########.##.##.#..##..#... 96 | ##..###..###....####.##.##..##.###....####..##...####.####..####..###.####..##.#...###.#####.##.##.# 97 | ###...##.#.#.#####..#..#####...##.#...#.#.###.#..##..###.##.#.#.....####.##.#..##.###.#...##.##...## 98 | ...#.#.##.##..##....#..#.#####.##.###..#.#.#........####.###.##....##....####..#.#....#.#.#.###..#.# 99 | ..#.#.#.#.###...#....##..######.##....#.#.##..###..#.#.###..#.##..#.#.###......#..#..#.####..#...##. 100 | .....####.#.....###.#.##.#..##.#..###.#####.#..##...###.#..###..#..##....###.#..##.#..#.##.#..#...## 101 | -------------------------------------------------------------------------------- /input19.txt: -------------------------------------------------------------------------------- 1 | Al => ThF 2 | Al => ThRnFAr 3 | B => BCa 4 | B => TiB 5 | B => TiRnFAr 6 | Ca => CaCa 7 | Ca => PB 8 | Ca => PRnFAr 9 | Ca => SiRnFYFAr 10 | Ca => SiRnMgAr 11 | Ca => SiTh 12 | F => CaF 13 | F => PMg 14 | F => SiAl 15 | H => CRnAlAr 16 | H => CRnFYFYFAr 17 | H => CRnFYMgAr 18 | H => CRnMgYFAr 19 | H => HCa 20 | H => NRnFYFAr 21 | H => NRnMgAr 22 | H => NTh 23 | H => OB 24 | H => ORnFAr 25 | Mg => BF 26 | Mg => TiMg 27 | N => CRnFAr 28 | N => HSi 29 | O => CRnFYFAr 30 | O => CRnMgAr 31 | O => HP 32 | O => NRnFAr 33 | O => OTi 34 | P => CaP 35 | P => PTi 36 | P => SiRnFAr 37 | Si => CaSi 38 | Th => ThCa 39 | Ti => BP 40 | Ti => TiTi 41 | e => HF 42 | e => NAl 43 | e => OMg 44 | 45 | CRnSiRnCaPTiMgYCaPTiRnFArSiThFArCaSiThSiThPBCaCaSiRnSiRnTiTiMgArPBCaPMgYPTiRnFArFArCaSiRnBPMgArPRnCaPTiRnFArCaSiThCaCaFArPBCaCaPTiTiRnFArCaSiRnSiAlYSiThRnFArArCaSiRnBFArCaCaSiRnSiThCaCaCaFYCaPTiBCaSiThCaSiThPMgArSiRnCaPBFYCaCaFArCaCaCaCaSiThCaSiRnPRnFArPBSiThPRnFArSiRnMgArCaFYFArCaSiRnSiAlArTiTiTiTiTiTiTiRnPMgArPTiTiTiBSiRnSiAlArTiTiRnPMgArCaFYBPBPTiRnSiRnMgArSiThCaFArCaSiThFArPRnFArCaSiRnTiBSiThSiRnSiAlYCaFArPRnFArSiThCaFArCaCaSiThCaCaCaSiRnPRnCaFArFYPMgArCaPBCaPBSiRnFYPBCaFArCaSiAl 46 | -------------------------------------------------------------------------------- /input2.txt: -------------------------------------------------------------------------------- 1 | 20x3x11 2 | 15x27x5 3 | 6x29x7 4 | 30x15x9 5 | 19x29x21 6 | 10x4x15 7 | 1x26x4 8 | 1x5x18 9 | 10x15x23 10 | 10x14x20 11 | 3x5x18 12 | 29x23x30 13 | 7x4x10 14 | 22x24x29 15 | 30x1x2 16 | 19x2x5 17 | 11x9x22 18 | 23x15x10 19 | 11x11x10 20 | 30x28x5 21 | 22x5x4 22 | 6x26x20 23 | 16x12x30 24 | 10x20x5 25 | 25x14x24 26 | 16x17x22 27 | 11x28x26 28 | 1x11x10 29 | 1x24x15 30 | 13x17x21 31 | 30x3x13 32 | 20x25x17 33 | 22x12x5 34 | 22x20x24 35 | 9x2x14 36 | 6x18x8 37 | 27x28x24 38 | 11x17x1 39 | 1x4x12 40 | 5x20x13 41 | 24x23x23 42 | 22x1x25 43 | 18x19x5 44 | 5x23x13 45 | 8x16x4 46 | 20x21x9 47 | 1x7x11 48 | 8x30x17 49 | 3x30x9 50 | 6x16x18 51 | 22x25x27 52 | 9x20x26 53 | 16x21x23 54 | 5x24x17 55 | 15x17x15 56 | 26x15x10 57 | 22x16x3 58 | 20x24x24 59 | 8x18x10 60 | 23x19x16 61 | 1x21x24 62 | 23x23x9 63 | 14x20x6 64 | 25x5x5 65 | 16x3x1 66 | 29x29x20 67 | 11x4x26 68 | 10x23x24 69 | 29x25x16 70 | 27x27x22 71 | 9x7x22 72 | 6x21x18 73 | 25x11x19 74 | 14x13x3 75 | 15x28x17 76 | 14x3x12 77 | 29x8x19 78 | 30x14x20 79 | 20x23x4 80 | 8x16x5 81 | 4x11x18 82 | 20x8x24 83 | 21x13x21 84 | 14x26x29 85 | 27x4x17 86 | 27x4x25 87 | 5x28x6 88 | 23x24x11 89 | 29x22x5 90 | 30x20x6 91 | 23x2x10 92 | 11x4x7 93 | 27x23x6 94 | 10x20x19 95 | 8x20x22 96 | 5x29x22 97 | 16x13x2 98 | 2x11x14 99 | 6x12x4 100 | 3x13x6 101 | 16x5x18 102 | 25x3x28 103 | 21x1x5 104 | 20x16x19 105 | 28x30x27 106 | 26x7x18 107 | 25x27x24 108 | 11x19x7 109 | 21x19x17 110 | 2x12x27 111 | 20x5x14 112 | 8x5x8 113 | 6x24x8 114 | 7x28x20 115 | 3x20x28 116 | 5x20x30 117 | 13x29x1 118 | 26x29x5 119 | 19x28x25 120 | 5x19x11 121 | 11x20x22 122 | 4x23x1 123 | 19x25x12 124 | 3x10x6 125 | 3x14x10 126 | 28x16x12 127 | 23x12x2 128 | 23x12x19 129 | 20x28x10 130 | 9x10x25 131 | 16x21x16 132 | 1x18x20 133 | 9x4x26 134 | 3x25x8 135 | 17x16x28 136 | 9x28x16 137 | 27x3x12 138 | 17x24x12 139 | 13x21x10 140 | 7x17x13 141 | 6x10x9 142 | 7x29x25 143 | 11x19x30 144 | 1x24x5 145 | 20x16x23 146 | 24x28x21 147 | 6x29x19 148 | 25x2x19 149 | 12x5x26 150 | 25x29x12 151 | 16x28x22 152 | 26x26x15 153 | 9x13x5 154 | 10x29x7 155 | 1x24x16 156 | 22x2x2 157 | 6x16x13 158 | 3x12x28 159 | 4x12x13 160 | 14x27x21 161 | 14x23x26 162 | 7x5x18 163 | 8x30x27 164 | 15x9x18 165 | 26x16x5 166 | 3x29x17 167 | 19x7x18 168 | 16x18x1 169 | 26x15x30 170 | 24x30x21 171 | 13x20x7 172 | 4x12x10 173 | 27x20x11 174 | 28x29x21 175 | 20x14x30 176 | 28x12x3 177 | 19x1x8 178 | 4x8x6 179 | 21x14x2 180 | 27x19x21 181 | 17x24x14 182 | 15x18x11 183 | 18x7x26 184 | 25x28x29 185 | 27x26x9 186 | 18x12x17 187 | 24x28x25 188 | 13x24x14 189 | 26x9x28 190 | 9x3x30 191 | 9x2x9 192 | 8x1x29 193 | 18x30x10 194 | 18x14x5 195 | 26x8x30 196 | 12x1x1 197 | 30x5x28 198 | 26x17x21 199 | 10x10x10 200 | 20x7x27 201 | 13x17x6 202 | 21x13x17 203 | 2x16x8 204 | 7x9x9 205 | 15x26x4 206 | 11x28x25 207 | 10x6x19 208 | 21x6x29 209 | 15x5x6 210 | 28x9x16 211 | 14x3x10 212 | 12x29x5 213 | 22x19x19 214 | 25x15x22 215 | 30x6x28 216 | 11x23x13 217 | 20x25x14 218 | 26x1x13 219 | 6x14x15 220 | 16x25x17 221 | 28x4x13 222 | 10x24x25 223 | 4x13x10 224 | 9x15x16 225 | 15x24x6 226 | 22x9x19 227 | 11x11x8 228 | 4x19x12 229 | 24x5x4 230 | 27x12x13 231 | 7x27x16 232 | 2x6x9 233 | 29x27x15 234 | 18x26x23 235 | 19x16x15 236 | 14x5x25 237 | 9x16x30 238 | 4x6x4 239 | 13x10x10 240 | 1x8x29 241 | 23x5x17 242 | 19x20x20 243 | 11x27x24 244 | 27x15x5 245 | 15x11x12 246 | 21x11x3 247 | 1x13x22 248 | 17x8x8 249 | 13x14x14 250 | 17x22x7 251 | 9x5x8 252 | 2x6x3 253 | 25x9x15 254 | 11x8x13 255 | 9x25x12 256 | 3x16x12 257 | 12x16x8 258 | 16x24x17 259 | 4x6x26 260 | 22x29x11 261 | 14x17x19 262 | 28x2x27 263 | 24x22x19 264 | 22x20x30 265 | 23x28x4 266 | 16x12x14 267 | 22x24x22 268 | 29x1x28 269 | 26x29x16 270 | 3x25x30 271 | 27x3x13 272 | 22x24x26 273 | 25x3x2 274 | 7x24x2 275 | 10x5x3 276 | 28x8x29 277 | 25x6x4 278 | 12x17x14 279 | 24x3x5 280 | 23x27x7 281 | 26x23x30 282 | 11x10x19 283 | 23x7x11 284 | 26x14x15 285 | 14x3x25 286 | 12x24x14 287 | 2x14x12 288 | 9x12x16 289 | 9x2x28 290 | 3x8x2 291 | 22x6x9 292 | 2x30x2 293 | 25x1x9 294 | 20x11x2 295 | 14x11x12 296 | 7x14x12 297 | 24x8x26 298 | 13x21x23 299 | 18x17x23 300 | 13x6x17 301 | 20x20x19 302 | 13x17x29 303 | 7x24x24 304 | 23x8x6 305 | 19x10x28 306 | 3x8x21 307 | 15x20x18 308 | 11x27x1 309 | 11x24x28 310 | 13x20x11 311 | 18x19x22 312 | 27x22x12 313 | 28x3x2 314 | 13x4x29 315 | 26x5x6 316 | 14x29x25 317 | 7x4x7 318 | 5x17x7 319 | 2x8x1 320 | 22x30x24 321 | 22x21x28 322 | 1x28x13 323 | 11x20x4 324 | 25x29x19 325 | 9x23x4 326 | 30x6x11 327 | 25x18x10 328 | 28x10x24 329 | 3x5x20 330 | 19x28x10 331 | 27x19x2 332 | 26x20x4 333 | 19x21x6 334 | 2x12x30 335 | 8x26x27 336 | 11x27x10 337 | 14x13x17 338 | 4x3x21 339 | 2x20x21 340 | 22x30x3 341 | 2x23x2 342 | 3x16x12 343 | 22x28x22 344 | 3x23x29 345 | 8x25x15 346 | 9x30x4 347 | 10x11x1 348 | 24x8x20 349 | 10x7x27 350 | 7x22x4 351 | 27x13x17 352 | 5x28x5 353 | 30x15x13 354 | 10x8x17 355 | 8x21x5 356 | 8x17x26 357 | 25x16x4 358 | 9x7x25 359 | 13x11x20 360 | 6x30x9 361 | 15x14x12 362 | 30x1x23 363 | 5x20x24 364 | 22x7x6 365 | 26x11x23 366 | 29x7x5 367 | 13x24x28 368 | 22x20x10 369 | 18x3x1 370 | 15x19x23 371 | 28x28x20 372 | 7x26x2 373 | 9x12x20 374 | 15x4x6 375 | 1x17x21 376 | 3x22x17 377 | 9x4x20 378 | 25x19x5 379 | 9x11x22 380 | 14x1x17 381 | 14x5x16 382 | 30x5x18 383 | 19x6x12 384 | 28x16x22 385 | 13x4x25 386 | 29x23x18 387 | 1x27x3 388 | 12x14x4 389 | 10x25x19 390 | 15x19x30 391 | 11x30x4 392 | 11x22x26 393 | 13x25x2 394 | 17x13x27 395 | 11x30x24 396 | 15x1x14 397 | 17x18x4 398 | 26x11x3 399 | 16x22x28 400 | 13x20x9 401 | 1x18x3 402 | 25x11x12 403 | 20x21x1 404 | 22x27x4 405 | 8x28x23 406 | 7x13x27 407 | 17x9x26 408 | 27x27x20 409 | 11x20x12 410 | 26x21x11 411 | 29x14x12 412 | 27x25x1 413 | 28x29x25 414 | 21x23x28 415 | 5x18x18 416 | 19x5x4 417 | 7x6x30 418 | 27x8x11 419 | 12x24x12 420 | 16x25x22 421 | 26x11x29 422 | 25x22x17 423 | 15x23x23 424 | 17x9x6 425 | 30x10x16 426 | 21x3x5 427 | 18x27x2 428 | 28x21x14 429 | 16x18x17 430 | 4x18x2 431 | 9x1x14 432 | 9x1x9 433 | 5x27x12 434 | 8x16x30 435 | 3x19x19 436 | 16x26x24 437 | 1x6x9 438 | 15x14x3 439 | 11x7x19 440 | 8x19x3 441 | 17x26x26 442 | 6x18x11 443 | 19x12x4 444 | 29x20x16 445 | 20x17x23 446 | 6x6x5 447 | 20x30x19 448 | 18x25x18 449 | 2x26x2 450 | 3x1x1 451 | 14x25x18 452 | 3x1x6 453 | 11x14x18 454 | 17x23x27 455 | 25x29x9 456 | 6x25x20 457 | 20x10x9 458 | 17x5x18 459 | 29x14x8 460 | 14x25x26 461 | 10x15x29 462 | 23x19x11 463 | 22x2x2 464 | 4x5x5 465 | 13x23x25 466 | 19x13x19 467 | 20x18x6 468 | 30x7x28 469 | 26x18x17 470 | 29x18x10 471 | 30x29x1 472 | 12x26x24 473 | 18x17x26 474 | 29x28x15 475 | 3x12x20 476 | 24x10x8 477 | 30x15x6 478 | 28x23x15 479 | 14x28x11 480 | 10x27x19 481 | 14x8x21 482 | 24x1x23 483 | 1x3x27 484 | 6x15x6 485 | 8x25x26 486 | 13x10x25 487 | 6x9x8 488 | 10x29x29 489 | 26x23x5 490 | 14x24x1 491 | 25x6x22 492 | 17x11x18 493 | 1x27x26 494 | 18x25x23 495 | 20x15x6 496 | 2x21x28 497 | 2x10x13 498 | 12x25x14 499 | 2x14x23 500 | 30x5x23 501 | 29x19x21 502 | 29x10x25 503 | 14x22x16 504 | 17x11x26 505 | 12x17x30 506 | 8x17x7 507 | 20x25x28 508 | 20x11x30 509 | 15x1x12 510 | 13x3x24 511 | 16x23x23 512 | 27x3x3 513 | 26x3x27 514 | 18x5x12 515 | 12x26x7 516 | 19x27x12 517 | 20x10x28 518 | 30x12x25 519 | 3x14x10 520 | 21x26x1 521 | 24x26x26 522 | 7x21x30 523 | 3x29x12 524 | 29x28x5 525 | 5x20x7 526 | 27x11x2 527 | 15x20x4 528 | 16x15x15 529 | 19x13x7 530 | 7x17x15 531 | 27x24x15 532 | 9x17x28 533 | 20x21x14 534 | 14x29x29 535 | 23x26x13 536 | 27x23x21 537 | 18x13x6 538 | 26x16x21 539 | 18x26x27 540 | 9x3x12 541 | 30x18x24 542 | 12x11x29 543 | 5x15x1 544 | 1x16x3 545 | 14x28x11 546 | 2x18x1 547 | 19x18x19 548 | 18x28x21 549 | 2x3x14 550 | 22x16x5 551 | 28x18x28 552 | 24x16x18 553 | 7x4x10 554 | 19x26x19 555 | 24x17x7 556 | 25x9x6 557 | 25x17x7 558 | 20x22x20 559 | 3x3x7 560 | 23x19x15 561 | 21x27x21 562 | 1x23x11 563 | 9x19x4 564 | 22x4x18 565 | 6x15x5 566 | 15x25x2 567 | 23x11x20 568 | 27x16x6 569 | 27x8x5 570 | 10x10x19 571 | 22x14x1 572 | 7x1x29 573 | 8x11x17 574 | 27x9x27 575 | 28x9x24 576 | 17x7x3 577 | 26x23x8 578 | 7x6x30 579 | 25x28x2 580 | 1x30x25 581 | 3x18x18 582 | 28x27x15 583 | 14x14x1 584 | 10x25x29 585 | 18x12x9 586 | 20x28x16 587 | 26x27x22 588 | 8x26x1 589 | 21x2x12 590 | 25x16x14 591 | 21x19x5 592 | 12x9x22 593 | 16x5x4 594 | 5x4x16 595 | 25x29x3 596 | 4x29x13 597 | 15x16x29 598 | 8x11x24 599 | 30x11x20 600 | 17x21x14 601 | 12x24x10 602 | 10x12x6 603 | 3x26x30 604 | 15x14x25 605 | 20x12x21 606 | 13x11x16 607 | 15x13x3 608 | 5x17x29 609 | 6x3x23 610 | 9x26x11 611 | 30x1x8 612 | 14x10x30 613 | 18x30x10 614 | 13x19x19 615 | 16x19x17 616 | 28x7x10 617 | 28x29x4 618 | 3x21x10 619 | 4x28x24 620 | 7x28x9 621 | 2x4x9 622 | 25x27x13 623 | 6x12x15 624 | 4x18x20 625 | 20x1x16 626 | 5x13x24 627 | 11x11x10 628 | 12x9x23 629 | 1x9x30 630 | 17x28x24 631 | 9x5x27 632 | 21x15x16 633 | 17x4x14 634 | 8x14x4 635 | 13x10x7 636 | 17x12x14 637 | 9x19x19 638 | 2x7x21 639 | 8x24x23 640 | 19x5x12 641 | 11x23x21 642 | 13x3x1 643 | 5x27x15 644 | 12x25x25 645 | 13x21x16 646 | 9x17x11 647 | 1x15x21 648 | 4x26x17 649 | 11x5x15 650 | 23x10x15 651 | 12x17x21 652 | 27x15x1 653 | 4x29x14 654 | 5x24x25 655 | 10x10x12 656 | 18x12x9 657 | 11x24x23 658 | 24x23x3 659 | 28x12x15 660 | 29x9x14 661 | 11x25x8 662 | 5x12x2 663 | 26x26x29 664 | 9x21x2 665 | 8x8x25 666 | 1x16x30 667 | 17x29x20 668 | 9x22x13 669 | 7x18x16 670 | 3x3x23 671 | 26x25x30 672 | 15x23x24 673 | 20x23x5 674 | 20x16x10 675 | 23x7x8 676 | 20x18x26 677 | 8x27x6 678 | 30x23x23 679 | 7x7x24 680 | 21x11x15 681 | 1x30x25 682 | 26x27x22 683 | 30x28x13 684 | 20x13x13 685 | 3x1x15 686 | 16x7x1 687 | 7x25x15 688 | 12x7x18 689 | 16x9x23 690 | 16x12x18 691 | 29x5x2 692 | 17x7x7 693 | 21x17x5 694 | 9x9x17 695 | 26x16x10 696 | 29x29x23 697 | 17x26x10 698 | 5x19x17 699 | 1x10x1 700 | 14x21x20 701 | 13x6x4 702 | 13x13x3 703 | 23x4x18 704 | 4x16x3 705 | 16x30x11 706 | 2x11x2 707 | 15x30x15 708 | 20x30x22 709 | 18x12x16 710 | 23x5x16 711 | 6x14x15 712 | 9x4x11 713 | 30x23x21 714 | 20x7x12 715 | 7x18x6 716 | 15x6x5 717 | 18x22x19 718 | 16x10x22 719 | 26x20x25 720 | 9x25x25 721 | 29x21x10 722 | 9x21x24 723 | 7x18x21 724 | 14x3x15 725 | 18x19x19 726 | 4x29x17 727 | 14x10x9 728 | 2x26x14 729 | 13x3x24 730 | 4x4x17 731 | 6x27x24 732 | 2x18x3 733 | 14x25x2 734 | 30x14x17 735 | 11x6x14 736 | 4x10x18 737 | 15x4x2 738 | 27x7x10 739 | 13x24x1 740 | 7x12x6 741 | 25x22x26 742 | 19x2x18 743 | 23x29x2 744 | 2x15x4 745 | 12x6x9 746 | 16x14x29 747 | 9x17x3 748 | 21x9x12 749 | 23x18x22 750 | 10x8x4 751 | 29x2x7 752 | 19x27x15 753 | 4x24x27 754 | 25x20x14 755 | 8x23x19 756 | 1x24x19 757 | 6x20x10 758 | 15x8x5 759 | 18x28x5 760 | 17x23x22 761 | 9x16x13 762 | 30x24x4 763 | 26x3x13 764 | 12x22x18 765 | 29x17x29 766 | 26x4x16 767 | 15x7x20 768 | 9x15x30 769 | 12x7x18 770 | 28x19x18 771 | 11x23x23 772 | 24x20x1 773 | 20x3x24 774 | 1x26x1 775 | 14x10x6 776 | 5x27x24 777 | 13x21x12 778 | 20x20x5 779 | 6x28x9 780 | 11x26x11 781 | 26x29x12 782 | 21x4x11 783 | 20x11x17 784 | 22x27x20 785 | 19x11x21 786 | 2x11x11 787 | 13x5x7 788 | 12x10x25 789 | 21x28x1 790 | 15x30x17 791 | 28x19x1 792 | 4x19x12 793 | 11x4x12 794 | 4x10x30 795 | 11x18x5 796 | 22x20x12 797 | 3x7x27 798 | 20x26x4 799 | 13x27x26 800 | 23x14x13 801 | 4x19x7 802 | 26x27x16 803 | 20x5x20 804 | 18x5x8 805 | 19x21x1 806 | 22x8x1 807 | 29x4x1 808 | 24x10x15 809 | 24x9x20 810 | 10x3x8 811 | 29x30x3 812 | 2x8x24 813 | 16x7x18 814 | 2x11x23 815 | 23x15x16 816 | 21x12x6 817 | 24x28x9 818 | 6x1x13 819 | 14x29x20 820 | 27x24x13 821 | 16x26x8 822 | 5x6x17 823 | 21x8x1 824 | 28x19x21 825 | 1x14x16 826 | 18x2x9 827 | 29x28x10 828 | 22x26x27 829 | 18x26x23 830 | 22x24x2 831 | 28x26x1 832 | 27x29x12 833 | 30x13x11 834 | 1x25x5 835 | 13x30x18 836 | 3x13x22 837 | 22x10x11 838 | 2x7x7 839 | 18x17x8 840 | 9x22x26 841 | 30x18x16 842 | 10x2x3 843 | 7x27x13 844 | 3x20x16 845 | 9x21x16 846 | 1x18x15 847 | 21x30x30 848 | 4x25x23 849 | 3x11x7 850 | 5x6x12 851 | 27x1x20 852 | 13x15x24 853 | 23x29x2 854 | 13x5x24 855 | 22x16x15 856 | 28x14x3 857 | 29x24x9 858 | 2x20x4 859 | 30x10x4 860 | 23x7x20 861 | 22x12x21 862 | 3x19x11 863 | 4x28x28 864 | 5x4x7 865 | 28x12x25 866 | 2x16x26 867 | 23x20x7 868 | 5x21x29 869 | 9x21x16 870 | 9x6x10 871 | 9x6x4 872 | 24x14x29 873 | 28x11x6 874 | 10x22x1 875 | 21x30x20 876 | 13x17x8 877 | 2x25x24 878 | 19x21x3 879 | 28x8x14 880 | 6x29x28 881 | 27x10x28 882 | 30x11x12 883 | 17x2x10 884 | 14x19x17 885 | 2x11x4 886 | 26x1x2 887 | 13x4x4 888 | 23x20x18 889 | 2x17x21 890 | 28x7x15 891 | 3x3x27 892 | 24x17x30 893 | 28x28x20 894 | 21x5x29 895 | 13x12x19 896 | 24x29x29 897 | 19x10x6 898 | 19x12x14 899 | 21x4x17 900 | 27x16x1 901 | 4x17x30 902 | 23x23x18 903 | 23x15x27 904 | 26x2x11 905 | 12x8x8 906 | 15x23x26 907 | 30x17x15 908 | 17x17x15 909 | 24x4x30 910 | 9x9x10 911 | 14x25x20 912 | 25x11x19 913 | 20x7x1 914 | 9x21x3 915 | 7x19x9 916 | 10x6x19 917 | 26x12x30 918 | 21x9x20 919 | 15x11x6 920 | 30x21x9 921 | 10x18x17 922 | 22x9x8 923 | 8x30x26 924 | 28x12x27 925 | 17x17x7 926 | 11x13x8 927 | 5x3x21 928 | 24x1x29 929 | 1x28x2 930 | 18x28x10 931 | 8x29x14 932 | 26x26x27 933 | 17x10x25 934 | 22x30x3 935 | 27x9x13 936 | 21x21x4 937 | 30x29x16 938 | 22x7x20 939 | 24x10x2 940 | 16x29x17 941 | 28x15x17 942 | 19x19x22 943 | 9x8x6 944 | 26x23x24 945 | 25x4x27 946 | 16x12x2 947 | 11x6x18 948 | 19x14x8 949 | 9x29x13 950 | 23x30x19 951 | 10x16x1 952 | 4x21x28 953 | 23x25x25 954 | 19x9x16 955 | 30x11x12 956 | 24x3x9 957 | 28x19x4 958 | 18x12x9 959 | 7x1x25 960 | 28x7x1 961 | 24x3x12 962 | 30x24x22 963 | 27x24x26 964 | 9x30x30 965 | 29x10x8 966 | 4x6x18 967 | 10x1x15 968 | 10x4x26 969 | 23x20x16 970 | 6x3x14 971 | 30x8x16 972 | 25x14x20 973 | 11x9x3 974 | 15x23x25 975 | 8x30x22 976 | 22x19x18 977 | 25x1x12 978 | 27x25x7 979 | 25x23x3 980 | 13x20x8 981 | 5x30x7 982 | 18x19x27 983 | 20x23x3 984 | 1x17x21 985 | 21x21x27 986 | 13x1x24 987 | 7x30x20 988 | 21x9x18 989 | 23x26x6 990 | 22x9x29 991 | 17x6x21 992 | 28x28x29 993 | 19x25x26 994 | 9x27x21 995 | 5x26x8 996 | 11x19x1 997 | 10x1x18 998 | 29x4x8 999 | 21x2x22 1000 | 14x12x8 1001 | -------------------------------------------------------------------------------- /input21.txt: -------------------------------------------------------------------------------- 1 | Hit Points: 104 2 | Damage: 8 3 | Armor: 1 4 | -------------------------------------------------------------------------------- /input22.txt: -------------------------------------------------------------------------------- 1 | Hit Points: 51 2 | Damage: 9 3 | -------------------------------------------------------------------------------- /input23.txt: -------------------------------------------------------------------------------- 1 | jio a, +22 2 | inc a 3 | tpl a 4 | tpl a 5 | tpl a 6 | inc a 7 | tpl a 8 | inc a 9 | tpl a 10 | inc a 11 | inc a 12 | tpl a 13 | inc a 14 | inc a 15 | tpl a 16 | inc a 17 | inc a 18 | tpl a 19 | inc a 20 | inc a 21 | tpl a 22 | jmp +19 23 | tpl a 24 | tpl a 25 | tpl a 26 | tpl a 27 | inc a 28 | inc a 29 | tpl a 30 | inc a 31 | tpl a 32 | inc a 33 | inc a 34 | tpl a 35 | inc a 36 | inc a 37 | tpl a 38 | inc a 39 | tpl a 40 | tpl a 41 | jio a, +8 42 | inc b 43 | jie a, +4 44 | tpl a 45 | inc a 46 | jmp +2 47 | hlf a 48 | jmp -7 49 | -------------------------------------------------------------------------------- /input24.txt: -------------------------------------------------------------------------------- 1 | 1 2 | 2 3 | 3 4 | 7 5 | 11 6 | 13 7 | 17 8 | 19 9 | 23 10 | 31 11 | 37 12 | 41 13 | 43 14 | 47 15 | 53 16 | 59 17 | 61 18 | 67 19 | 71 20 | 73 21 | 79 22 | 83 23 | 89 24 | 97 25 | 101 26 | 103 27 | 107 28 | 109 29 | 113 30 | -------------------------------------------------------------------------------- /input25.txt: -------------------------------------------------------------------------------- 1 | To continue, please consult the code grid in the manual. Enter the code at row 3010, column 3019. 2 | -------------------------------------------------------------------------------- /input3.txt: -------------------------------------------------------------------------------- 1 | v>vvv>v<<<^^^^^<<^^>v^>^>^>^>^>^<<^><<<^vvvv>^>^><^v^><^<>^^>^vvv^>^>^^<>><>^>vvv>>^vv>^<><>^^>^>><<^><><>^<^>>vvv>v>>>v<<^<><^v>^^v^^^<^v^^>>><^>^>v<>^<>>^>^^v^>>><>v^v<>>^>^<>v^>^<>^v^^^v^^>>vv<<^^><^^>^^<^>>^^^^^v^vv<>>v^v<^v^^<><^<^vv^><>><><>v>vvv^vv^^<<><<<^v^>vvv^<^>vvvv^>^>>^v^v>vv^<>><^^^>^>>v>^>v^<>v><^<^^^vv<^^<>v^v^vv<>>>>v^v<>><^^v>vv^^>v^v>v>v>>vv>^^>^v><<^<vv^^^v>v^^^>><^^>v>^^v>>v^^^<^^v>^v>><^<^<>>v<<^^vv>^^^v<^<^^vv^>>v^>><<<>^vv^<^<>v^^<<^><>>^^^<^vv<^^^>><^^v>^^v^^^^<^v<^<<<<^v^<^^<>^^>^><<>>^v><>><^<^^^>>vv>^>^^^^^v^vvv><><^<^>v>v^v^>^><><^<^><>v<><>^v^^v>^<<<>^v^>^<v^<>>^vv>v>>>^<^>>>>>v>>^v>v><>>vvv<^^><<^>^>v<^vvvv<^^^v^^^>v^v<>v<^^v>>><>v>v>>^^<^^v><<<<<^vv<^<>^>>>^v>^v>vv>^v<>v>v<^>>v>>^>^><^^v<><><^^>^^^^>vv^v^v>^v^^v^^v>><^v>>vv<>vvvv<>>^v^>^>>v^v^<<>>^v<^^vv^><>v>^>v><<<<<<<^>^^v^<<^^>>vvv^<><>><>^^v<<^^v<^^>v^>>>v^v>v^><>v<<>v>^^v><<<<><^v^v>>^<>^<<>^>v<<>><^<<<<^v>^<^v>v>vv^>v<^<<>v^v>><v>v>>v^vvv^^>>>v^<^<<^^<<<>v^<v<^^<>^>v>>v<>^>^^>>^v<<>v^^^>>>^vv<^v^>v>^><>v^^<>^^v^^vv^<^>^<<>><<^>^v>>><<<<><<^v>v^<^><^<>>v^>^^^<>>v<>>^>>v^><<>vvv><^>>v><>v>>^>v><<><<>^<>^^^vv>v^^>>^>^<^vv^>v^>^><^<^><><v<^^v^^<<<<^><^^<^><>>^v<<^<<^vv>v>>v<^<^vv>>v^v<>^>v<>^v<<>^^v>>>v^>^v^v>^^^v><^>vvv^<<<>v<>v>^>vv^<^^v^><^^^^^v<^>>vv^v^>^^<>>><^v^<v>^v>^^v<>>vv>>^v>>^<<<<^><<<><^^>>v<>^vvvv>v^^^>^^^>^<^^vv<^v^v<v^^<>^>^<^v>vvv><<^><><^^v<<><^^><>^v>^<><<^<^^<<>vv<>^^<<^>><<<>>vvv>^>v^^v^><<^>v>^>^<^<<>v<^>vv^v^v<>vv<vv<^>v^<>^vv^v^>>>v^v><^<><<>vv^>vvv^>v>>><^^vvv<^<^>>^^>^^vv>>><^v<>^v^<<>v^^^^>>^<^>^v<^^^^v>^>>v>^>^>>>v^<<^>^<<^^<>v<^v<^<>v^v>^^v^vv>vvv>v^<^>>vvvv<>>^^<>v^<><>v<^<>v<>^>v<>vv>v<^^>v>><>>^<^^<>>^>^>vvv^v>>^>^>v><><<>v<>^v<^vv^^^<>^^<<^^^v<>>v^>vvvv>^^v^>^>^<<><^^^^<<>^<>vv^<><^>^^<>v^<>>>v><>vvvvv>v>v^^>^<vv>>v<<^<>^^^v^<><>>^<<>>><>v>^>^^^^vv^^<<><^^<v>vv<<<^<v<>>^<^>^>>v>><^^<>><<<><<><^<^v<^^v<<>><<<<^>v^>v^v^<<>>v<><^<>><>>^><>v^v>v<<>v<>v^^><<>>>v<<>>>>^>v>>>>vv>v>^<^^^<>v^<^^v^vvv^>vv>^^<<>vvv<<^^<^>^>>v>v<<<<<>^^vv^>>v>^<^^v>>v>^v<><>^<^>v>v<<<^^^v>^<<<>vvv^v^^>^>>^>v>v<>^^><>>v>^>v<<<^^^v^><><^<^<>>^v>vv<^v<<^vv>v^<v>v>^v^>^v<<^v^vv>v^<<>>v<>>vvv^^vv^^v><^>v^vv<^^<<>v<><^><>^<><vv<>^vv>v><^^v<>><^v^v><><>>vv<>>>><<^>>><^^^vvv<<><>>>v<<<<<>v^^<<^vv^>vv>^<>^v^^<>^^^vv>v^^v>^v>^<>v^^^>v^^v<^>v^v^<>v>v>v<^^vv^v<^^^^vv<<><<^>>^^<v^>>^^^><^^>^v^v>^<^>>^v<>^<^>v>^>^v^<^^^<^vv<^^>>v^>^v^>>>>^v>^^<<^<^^v^<<<>>><>^<>>>v<<><<^^<^^>v^>^>v^v<><^^v>^<^v^v>>>^^<^^vv<<^><><^<>v>>>vv>><^^^v^^^v<^^v>v<>>^^<><>v>^^>>>><>v>^v>^vv^v>^>^^^><>^<<>>><<<><>^^<<v^>v>v^^^>^>^v<<>v>vv>><<^^^>>^><^>v<^<^v>><^^>v<><>^><<><>v^>v<><^^>><>^<^^v<^<><<<^^<><>>>^>v^<><^<<^vv<^v^v^v<>v^^v>v^<^>^vv^>>><<>v^vv^<>^v^><v^<><>>v^v^><>v^vvv^^^<<^<>v^v>^^><>v>>v^<>^>v>^>><<>v^v><^v>v>>><^<^^>vv<^>^<^>^^v><><^<<^^vvv^v>^>^<>>vv>v^^v^^vv<^^>><^v>v^<vvv<>>^v><<>^v<<<>^><^vv><<^^v<^vv<>^v>>>><<<<^^<^v>^<^^<^<^^>>^^v>^^^^v^^^<<>^^vv<><^<<><>^>v<>>v^^^>^v^^v^v>>>>>^v>^>^^v>><^^^v<<^^>^<^<^><^<<>v>v>^v<><^>vv^vv><^><>^><<^^>v>v>^^^<>v>^v^^>vv^vv<^^>><>^>^<>v>><>^v<v>^><^^^v^<<^v^>v^>vv>v^<>v><^v>v<>^v<>^v>^^<>vvv^>^<><^>><^<>^v<<^v^><<^<^v>^vv^v>v<^^vv<><>vv^>v<<>v>v>^^>>><<<^>^vv>>^^^>v<^vv<>v<<>>>^<^^^^>v<^^<>v>vvv^>v>v<^>^v^<>v>>vvv>^^><^vvv>><>>>^<<^>>v^^>>^><>v<^^v^<<>^<>>><^v^v>>>^vvvv^<><<>v>^v^v>v><^<<^>^^>v<^v^<^>v>^<v^<>v^<>vv^<>^>^>v^>^vv<>^^<<>>v<>^v<><><<v>v^>vv^><<<^v<><>^^v^^v^^^>^<>>>>^><>>v>>v<<>v<<<<<<<^v<<^^^v<^v<>v^^<<<^<>>v^vv^<^^<^^<<^>vv><^<^^v<<<^><^v<^><>v^v^^>>><<^<<^<>>^>>^<<<>>v>^v>><>v>>v>><>v>><^^>^^vv<^^<^>vv><<^>><<>^vvv><^v^>vvv^>>^<><^>^<<>>v^v>v<<>^>>^>v<^^<^<<>^^v^^v>v<>^<^^<v^^vvv^^v>^vv^<>v<^v^>^vv<v^<<^>^><^^<^^<^>vv^<>^<>^>^^<^v><<<^>vv^vv>v^v<>^^v^<^^^vvv^>v^<><>v>vv<^v^>>^v<^^vv>vv>^>><<<<>^><>>v<>>v>^v<^vv>^^>^<^<>v^v<^^v<^^>^^<>^^^^>^vv<^>><^>vv^>v^>^vv>^>v^^<>>^v<>>v<^>^v>vv^>^>>>vvv>vv>^><^v<<<>^^v>v^v<^^^v^^>^><<^^>^><^^^^^^^<^v<^>>vv>>^v^vv<>><>^>>>^^^^^><^<<^v<>vv^>>v<^vv<^v<>v<>^v^<<>>>>v^^>^vv<<><<>v^v<^<^>>^^><^>^><<><^<><>vv>>>>^><<^^^<^v^>^>^^>^<^><^^<^^<>><>><<<>^>^^v<>^<<>vv>^>>^>^<>>vv<^^vv<>v<>^^>^v^v^v>^^^v<<<^vv^><>^>^^vv>v^<<^><>>vv^^^^^>v>>v<<<>^<><^v<^v<^>^<>^vvv>^>v><<v>vv^<^^>v^v>^<^v^<^v<<^>^<><>^^<>>^^<^v^<^<<^>v^^>v^v^^^<^v<<^v>^>>^^^^^><<>v^><>v^^<^v<^<v^^^><^^^><<<<<>^<<^<>>v<^>><^^^<>>>>vvv>v<>>>v^v^v<^<<^>^<<>v>>^>^^><^><<^v^^<^<>v^v>vv<>>>>>>v<<>>^^>v<<<>^<<^><<^v>vv>>>><><>v^<^v><^>v>>^^^v<^>>^>>v<<^<<>vvv>>^v<>>^v><<<^v^v<>^vvv^^^<>vvv^^^>>v>^>^<><<>vv>^v^>>^<v><><<>^^><>^<<>^v<<>>v^vv<<>^^v^v^v><^>v>v<^<<^<^>vv>^v<<^>^>>v^<v^^v^^>><<<>^v>><>v<>><^v>^^v<<<<^v^vv<<<<><><^<^<^v><<^^v^<<<<<^^><^^>vvv<^><>vvv^v^>^>^^^v<<^<^^>vv^vv^><^v^<<>v<^^>^vv<<>^<<><^>v^<<^<>v><><>v<<^^><^^^v>>v>^vv>^v^^<><<<<<^>^v^<^<^^>^vv<^>v^^v^<>v<>v^v>vvv><><<><>vv^^>^^^<><^>^^^>vvv><>v<>>v^>v^^vv^>v>>>><^^>^v^v>>vv<^>><<<^>><^<^>^<^>^>>v^<^<>^<^^<>^<>>><^<^<^<<^><^^>vv<>^^>v^>>v>>>v<<^vv^<><>>>^^<^v^>>^>>><<^<>^>>^v>>><^^^<<^vv><><<>^^^<>^^^>><>>>^>vv>^<^<>>^<^^>v^>vv><><>>><><<^^v<<^vvv<><><<^v>^v<>^<^^^v^>^<^><^v>v>^v<>><^^v^^^^^<>>vvvv>>>>^<<><^v>vv>>^^><<><><^^^<^<^<<^v>^^^>>>>><v^^^<>>vv^^^v<><^>v>><<><>v<^><<>>><>v>^<>>^>v^v<<<<>^vv<<>>>>>vv<><>^<^v>vv^<>><<>^<>><^>>>><<>^^>><<<^^^^^v>>^<<>>vvvv<^v^vvv<<<^><>>>>vv^<^v>v<^<>^v>>^<^^v^>>><>^^<^v>>v<<>vvvv>^><>v^<>^<<^vv<^>>^v^>^^<<<^>>^^>^<^^<^<<v^^v^^<^v<^>>><<>vv<<^><^>vv<^>>^vv>>>^>>><^<<<>>^<<>><^<<^^^>>v^^>v<<<>v>v>v^<>>>^vvv><<^^<<><^v>>>>vv^^v^v<>v>v<<<<><<>vv<><^^^<>>v>>>>^^<><^<^v^>>^^v>^<v>^^>^v^<>>v^^<^v^^<<>^^>v^^>><<<<^<^^v>^^v>v<^>v^<>vv>>^^v>v^^>vvvvv<<>vv>vvvvvv>>v>>^^^vv^^><>v^^^^v>vv>v<^v>>>>^>^>^v>^>>><<>>^vv>>>><><<^<^><^vv^v>>>>>v>^>^^v^>v<^v^<^<v<>>^vv<<>^v^v>><><<>>v^^<<>^^<>v<<^^<^^>^^>^<^><>>v<>>^^<^>><<>>^v^>v>v<<^^<<^>v>v^^v^^<<>^v>v>v<^^>^v<><^<<v<^<<<<^^>v^v^^><<><^^^v^^>>>vvv><>vv<>>^^v^v<<^>v^^v^>vv>^<^^<^v^^<^^v<<>>vv<^>>^><><>v>>v<>^<<>>> -------------------------------------------------------------------------------- /input4.txt: -------------------------------------------------------------------------------- 1 | yzbqklnj 2 | -------------------------------------------------------------------------------- /input5.txt: -------------------------------------------------------------------------------- 1 | zgsnvdmlfuplrubt 2 | vlhagaovgqjmgvwq 3 | ffumlmqwfcsyqpss 4 | zztdcqzqddaazdjp 5 | eavfzjajkjesnlsb 6 | urrvucyrzzzooxhx 7 | xdwduffwgcptfwad 8 | orbryxwrmvkrsxsr 9 | jzfeybjlgqikjcow 10 | mayoqiswqqryvqdi 11 | iiyrkoujhgpgkcvx 12 | egcgupjkqwfiwsjl 13 | zbgtglaqqolttgng 14 | eytquncjituzzhsx 15 | dtfkgggvqadhqbwb 16 | zettygjpcoedwyio 17 | rwgwbwzebsnjmtln 18 | esbplxhvzzgawctn 19 | vnvshqgmbotvoine 20 | wflxwmvbhflkqxvo 21 | twdjikcgtpvlctte 22 | minfkyocskvgubvm 23 | sfxhhdhaopajbzof 24 | sofkjdtalvhgwpql 25 | uqfpeauqzumccnrc 26 | tdflsbtiiepijanf 27 | dhfespzrhecigzqb 28 | xobfthcuuzhvhzpn 29 | olgjglxaotocvrhw 30 | jhkzpfcskutwlwge 31 | zurkakkkpchzxjhq 32 | hekxiofhalvmmkdl 33 | azvxuwwfmjdpjskj 34 | arsvmfznblsqngvb 35 | ldhkzhejofreaucc 36 | adrphwlkehqkrdmo 37 | wmveqrezfkaivvaw 38 | iyphmphgntinfezg 39 | blomkvgslfnvspem 40 | cgpaqjvzhbumckwo 41 | ydhqjcuotkeyurpx 42 | sbtzboxypnmdaefr 43 | vxrkhvglynljgqrg 44 | ttgrkjjrxnxherxd 45 | hinyfrjdiwytetkw 46 | sufltffwqbugmozk 47 | tohmqlzxxqzinwxr 48 | jbqkhxfokaljgrlg 49 | fvjeprbxyjemyvuq 50 | gmlondgqmlselwah 51 | ubpwixgxdloqnvjp 52 | lxjfhihcsajxtomj 53 | qouairhvrgpjorgh 54 | nloszcwcxgullvxb 55 | myhsndsttanohnjn 56 | zjvivcgtjwenyilz 57 | qaqlyoyouotsmamm 58 | tadsdceadifqthag 59 | mafgrbmdhpnlbnks 60 | aohjxahenxaermrq 61 | ovvqestjhbuhrwlr 62 | lnakerdnvequfnqb 63 | agwpwsgjrtcjjikz 64 | lhlysrshsmzryzes 65 | xopwzoaqtlukwwdu 66 | xsmfrfteyddrqufn 67 | ohnxbykuvvlbbxpf 68 | bbdlivmchvzfuhoc 69 | vtacidimfcfyobhf 70 | tinyzzddgcnmiabd 71 | tcjzxftqcqrivqhn 72 | vgnduqyfpokbmzim 73 | revkvaxnsxospyow 74 | ydpgwxxoxlywxcgi 75 | wzuxupbzlpzmikel 76 | nscghlafavnsycjh 77 | xorwbquzmgmcapon 78 | asmtiycegeobfxrn 79 | eqjzvgkxgtlyuxok 80 | mmjrskloposgjoqu 81 | gceqosugbkvytfto 82 | khivvoxkvhrgwzjl 83 | qtmejuxbafroifjt 84 | ttmukbmpoagthtfl 85 | bxqkvuzdbehtduwv 86 | gvblrpzjylanoggj 87 | cltewhyjxdbmbtqj 88 | fbkgedqvomdipklj 89 | uxvuplhenqawfcjt 90 | fkdjmayiawdkycva 91 | gnloqfgbnibzyidh 92 | kyzorvtopjiyyyqg 93 | drckpekhpgrioblt 94 | tvhrkmbnpmkkrtki 95 | khaldwntissbijiz 96 | aoojqakosnaxosom 97 | xfptccznbgnpfyqw 98 | moqdwobwhjxhtrow 99 | chfwivedutskovri 100 | gprkyalfnpljcrmi 101 | pwyshpwjndasykst 102 | xuejivogihttzimd 103 | bugepxgpgahtsttl 104 | zufmkmuujavcskpq 105 | urybkdyvsrosrfro 106 | isjxqmlxwtqmulbg 107 | pxctldxgqjqhulgz 108 | hclsekryiwhqqhir 109 | hbuihpalwuidjpcq 110 | ejyqcxmfczqfhbxa 111 | xljdvbucuxnnaysv 112 | irqceqtqwemostbb 113 | anfziqtpqzqdttnz 114 | cgfklbljeneeqfub 115 | zudyqkuqqtdcpmuo 116 | iuvhylvznmhbkbgg 117 | mpgppmgfdzihulnd 118 | argwmgcvqqkxkrdi 119 | pdhrfvdldkfihlou 120 | cbvqnjrvrsnqzfob 121 | lkvovtsqanohzcmm 122 | vxoxjdyoylqcnyzt 123 | kurdpaqiaagiwjle 124 | gwklwnazaxfkuekn 125 | rbaamufphjsjhbdl 126 | tzbrvaqvizhsisbd 127 | pbcqlbfjvlideiub 128 | hiwoetbfywaeddtx 129 | fjirczxtuupfywyf 130 | omeoegeyyospreem 131 | ozbbpupqpsskvrjh 132 | pzvcxkvjdiyeyhxa 133 | odclumkenabcsfzr 134 | npdyqezqdjqaszvm 135 | yodkwzmrhtexfrqa 136 | rjcmmggjtactfrxz 137 | mioxfingsfoimual 138 | aqskaxjjborspfaa 139 | wientdsttkevjtkf 140 | tdaswkzckmxnfnct 141 | voucjhzvkkhuwoqk 142 | boaaruhalgaamqmh 143 | iufzxutxymorltvb 144 | pfbyvbayvnrpijpo 145 | obztirulgyfthgcg 146 | ntrenvhwxypgtjwy 147 | ephlkipjfnjfjrns 148 | pkjhurzbmobhszpx 149 | gqbnjvienzqfbzvj 150 | wjelolsrbginwnno 151 | votanpqpccxqricj 152 | bxyuyiglnmbtvehi 153 | qyophcjfknbcbjrb 154 | anoqkkbcdropskhj 155 | tcnyqaczcfffkrtl 156 | rsvqimuqbuddozrf 157 | meppxdrenexxksdt 158 | tyfhfiynzwadcord 159 | wayrnykevdmywycf 160 | mhowloqnppswyzbu 161 | tserychksuwrgkxz 162 | xycjvvsuaxsbrqal 163 | fkrdsgaoqdcqwlpn 164 | vrabcmlhuktigecp 165 | xgxtdsvpaymzhurx 166 | ciabcqymnchhsxkc 167 | eqxadalcxzocsgtr 168 | tsligrgsjtrnzrex 169 | qeqgmwipbspkbbfq 170 | vzkzsjujltnqwliw 171 | ldrohvodgbxokjxz 172 | jkoricsxhipcibrq 173 | qzquxawqmupeujrr 174 | mizpuwqyzkdbahvk 175 | suupfxbtoojqvdca 176 | ywfmuogvicpywpwm 177 | uevmznxmsxozhobl 178 | vjbyhsemwfwdxfxk 179 | iyouatgejvecmtin 180 | tcchwpuouypllcxe 181 | lgnacnphdiobdsef 182 | uoxjfzmdrmpojgbf 183 | lqbxsxbqqhpjhfxj 184 | knpwpcnnimyjlsyz 185 | fezotpoicsrshfnh 186 | dkiwkgpmhudghyhk 187 | yzptxekgldksridv 188 | pckmzqzyiyzdbcts 189 | oqshafncvftvwvsi 190 | yynihvdywxupqmbt 191 | iwmbeunfiuhjaaic 192 | pkpkrqjvgocvaxjs 193 | ieqspassuvquvlyz 194 | xshhahjaxjoqsjtl 195 | fxrrnaxlqezdcdvd 196 | pksrohfwlaqzpkdd 197 | ravytrdnbxvnnoyy 198 | atkwaifeobgztbgo 199 | inkcabgfdobyeeom 200 | ywpfwectajohqizp 201 | amcgorhxjcybbisv 202 | mbbwmnznhafsofvr 203 | wofcubucymnhuhrv 204 | mrsamnwvftzqcgta 205 | tlfyqoxmsiyzyvgv 206 | ydceguvgotylwtea 207 | btyvcjqhsygunvle 208 | usquiquspcdppqeq 209 | kifnymikhhehgote 210 | ybvkayvtdpgxfpyn 211 | oulxagvbavzmewnx 212 | tvvpekhnbhjskzpj 213 | azzxtstaevxurboa 214 | nfmwtfgrggmqyhdf 215 | ynyzypdmysfwyxgr 216 | iaobtgubrcyqrgmk 217 | uyxcauvpyzabbzgv 218 | fbasfnwiguasoedc 219 | mgmjoalkbvtljilq 220 | szgkxiqkufdvtksb 221 | xgfzborpavdmhiuj 222 | hmuiwnsonvfgcrva 223 | zolcffdtobfntifb 224 | mvzgcsortkugvqjr 225 | pbbpgraaldqvzwhs 226 | zvsxegchksgnhpuv 227 | kdpdboaxsuxfswhx 228 | jdfggigejfupabth 229 | tpeddioybqemyvqz 230 | mxsntwuesonybjby 231 | tzltdsiojfvocige 232 | ubtdrneozoejiqrv 233 | fusyucnhncoxqzql 234 | nlifgomoftdvkpby 235 | pyikzbxoapffbqjw 236 | hzballplvzcsgjug 237 | ymjyigsfehmdsvgz 238 | vpqgyxknniunksko 239 | ffkmaqsjxgzclsnq 240 | jcuxthbedplxhslk 241 | ymlevgofmharicfs 242 | nyhbejkndhqcoisy 243 | rjntxasfjhnlizgm 244 | oqlnuxtzhyiwzeto 245 | tntthdowhewszitu 246 | rmxyoceuwhsvfcua 247 | qpgsjzwenzbxyfgw 248 | sumguxpdkocyagpu 249 | ymfrbxwrawejkduu 250 | hetgrtmojolbmsuf 251 | qzqizpiyfasgttex 252 | qnmoemcpuckzsshx 253 | ddyqiihagcmnxccu 254 | oirwxyfxxyktgheo 255 | phpaoozbdogbushy 256 | uctjdavsimsrnvjn 257 | aurbbphvjtzipnuh 258 | hpbtrubopljmltep 259 | pyyvkthqfsxqhrxg 260 | jdxaiqzkepxbfejk 261 | ukgnwbnysrzvqzlw 262 | lfkatkvcssnlpthd 263 | ucsyecgshklhqmsc 264 | rwdcbdchuahkvmga 265 | rxkgqakawgpwokum 266 | hbuyxeylddfgorgu 267 | tbllspqozaqzglkz 268 | rqfwizjlbwngdvvi 269 | xuxduyzscovachew 270 | kouiuxckkvmetvdy 271 | ycyejrpwxyrweppd 272 | trctlytzwiisjamx 273 | vtvpjceydunjdbez 274 | gmtlejdsrbfofgqy 275 | jgfbgtkzavcjlffj 276 | tyudxlpgraxzchdk 277 | gyecxacqitgozzgd 278 | rxaocylfabmmjcvt 279 | tornfzkzhjyofzqa 280 | kocjcrqcsvagmfqv 281 | zfrswnskuupivzxb 282 | cunkuvhbepztpdug 283 | pmpfnmklqhcmrtmf 284 | tfebzovjwxzumxap 285 | xpsxgaswavnzkzye 286 | lmwijdothmxclqbr 287 | upqxhmctbltxkarl 288 | axspehytmyicthmq 289 | xdwrhwtuooikehbk 290 | tpggalqsytvmwerj 291 | jodysbwnymloeqjf 292 | rxbazvwuvudqlydn 293 | ibizqysweiezhlqa 294 | uexgmotsqjfauhzp 295 | ldymyvumyhyamopg 296 | vbxvlvthgzgnkxnf 297 | pyvbrwlnatxigbrp 298 | azxynqididtrwokb 299 | lwafybyhpfvoawto 300 | ogqoivurfcgspytw 301 | cinrzzradwymqcgu 302 | sgruxdvrewgpmypu 303 | snfnsbywuczrshtd 304 | xfzbyqtyxuxdutpw 305 | fmpvjwbulmncykbo 306 | ljnwoslktrrnffwo 307 | ceaouqquvvienszn 308 | yjomrunrxjyljyge 309 | xpmjsapbnsdnbkdi 310 | uetoytptktkmewre 311 | eixsvzegkadkfbua 312 | afaefrwhcosurprw 313 | bwzmmvkuaxiymzwc 314 | gejyqhhzqgsrybni 315 | gjriqsfrhyguoiiw 316 | gtfyomppzsruhuac 317 | ogemfvmsdqqkfymr 318 | jgzbipsygirsnydh 319 | zghvlhpjnvqmocgr 320 | ngvssuwrbtoxtrka 321 | ietahyupkbuisekn 322 | gqxqwjizescbufvl 323 | eiprekzrygkncxzl 324 | igxfnxtwpyaamkxf 325 | soqjdkxcupevbren 326 | fspypobyzdwstxak 327 | qstcgawvqwtyyidf 328 | gsccjacboqvezxvd 329 | bfsblokjvrqzphmc 330 | srezeptvjmncqkec 331 | opmopgyabjjjoygt 332 | msvbufqexfrtecbf 333 | uiaqweyjiulplelu 334 | pbkwhjsibtwjvswi 335 | xwwzstmozqarurrq 336 | nytptwddwivtbgyq 337 | ejxvsufbzwhzpabr 338 | jouozvzuwlfqzdgh 339 | gfgugjihbklbenrk 340 | lwmnnhiuxqsfvthv 341 | bzvwbknfmaeahzhi 342 | cgyqswikclozyvnu 343 | udmkpvrljsjiagzi 344 | zzuhqokgmisguyna 345 | ekwcdnjzuctsdoua 346 | eueqkdrnzqcaecyd 347 | lnibwxmokbxhlris 348 | fdrbftgjljpzwhea 349 | iabvuhhjsxmqfwld 350 | qgogzkynrgejakta 351 | mfcqftytemgnpupp 352 | klvhlhuqhosvjuqk 353 | gdokmxcgoqvzvaup 354 | juududyojcazzgvr 355 | fyszciheodgmnotg 356 | yfpngnofceqfvtfs 357 | cahndkfehjumwavc 358 | dxsvscqukljxcqyi 359 | cqukcjtucxwrusji 360 | vevmmqlehvgebmid 361 | ahswsogfrumzdofy 362 | ftasbklvdquaxhxb 363 | tsdeumygukferuif 364 | ybfgbwxaaitpwryg 365 | djyaoycbymezglio 366 | trzrgxdjqnmlnzpn 367 | rumwchfihhihpqui 368 | ffrvnsgrnzemksif 369 | oizlksxineqknwzd 370 | cirqcprftpjzrxhk 371 | zrhemeqegmzrpufd 372 | kqgatudhxgzlgkey 373 | syjugymeajlzffhq 374 | nlildhmgnwlopohp 375 | flcszztfbesqhnyz 376 | ohzicmqsajyqptrw 377 | ebyszucgozsjbelq 378 | enxbgvvcuqeloxud 379 | ubwnvecbsmhkxwuk 380 | noifliyxvlkqphbo 381 | hazlqpetgugxxsiz 382 | ihdzoerqwqhgajzb 383 | ivrdwdquxzhdrzar 384 | synwycdvrupablib 385 | mqkdjkntblnmtvxj 386 | qmmvoylxymyovrnq 387 | pjtuxskkowutltlq 388 | gchrqtloggkrjciz 389 | namzqovvsdipazae 390 | yfokqhkmakyjzmys 391 | iapxlbuoiwqfnozm 392 | fbcmlcekgfdurqxe 393 | ednzgtczbplwxjlq 394 | gdvsltzpywffelsp 395 | oaitrrmpqdvduqej 396 | gseupzwowmuuibjo 397 | dfzsffsqpaqoixhh 398 | tclhzqpcvbshxmgx 399 | cfqkptjrulxiabgo 400 | iraiysmwcpmtklhf 401 | znwjlzodhktjqwlm 402 | lcietjndlbgxzjht 403 | gdkcluwjhtaaprfo 404 | vbksxrfznjzwvmmt 405 | vpfftxjfkeltcojl 406 | thrmzmeplpdespnh 407 | yafopikiqswafsit 408 | xxbqgeblfruklnhs 409 | qiufjijzbcpfdgig 410 | ikksmllfyvhyydmi 411 | sknufchjdvccccta 412 | wpdcrramajdoisxr 413 | grnqkjfxofpwjmji 414 | lkffhxonjskyccoh 415 | npnzshnoaqayhpmb 416 | fqpvaamqbrnatjia 417 | oljkoldhfggkfnfc 418 | ihpralzpqfrijynm 419 | gvaxadkuyzgbjpod 420 | onchdguuhrhhspen 421 | uefjmufwlioenaus 422 | thifdypigyihgnzo 423 | ugqblsonqaxycvkg 424 | yevmbiyrqdqrmlbw 425 | bvpvwrhoyneorcmm 426 | gbyjqzcsheaxnyib 427 | knhsmdjssycvuoqf 428 | nizjxiwdakpfttyh 429 | nwrkbhorhfqqoliz 430 | ynsqwvwuwzqpzzwp 431 | yitscrgexjfclwwh 432 | dhajwxqdbtrfltzz 433 | bmrfylxhthiaozpv 434 | frvatcvgknjhcndw 435 | xlvtdmpvkpcnmhya 436 | pxpemuzuqzjlmtoc 437 | dijdacfteteypkoq 438 | knrcdkrvywagglnf 439 | fviuajtspnvnptia 440 | xvlqzukmwbcjgwho 441 | bazlsjdsjoeuvgoz 442 | nslzmlhosrjarndj 443 | menvuwiuymknunwm 444 | uavfnvyrjeiwqmuu 445 | yrfowuvasupngckz 446 | taevqhlrcohlnwye 447 | skcudnogbncusorn 448 | omtnmkqnqedsajfv 449 | yqmgsqdgsuysqcts 450 | odsnbtyimikkbmdd 451 | vuryaohxdvjllieb 452 | dhaxldeywwsfamlo 453 | opobvtchezqnxpak 454 | pzfnegouvsrfgvro 455 | rzkcgpxdslzrdktu 456 | ksztdtqzxvhuryam 457 | ctnqnhkcooqipgkh 458 | pyqbbvrzdittqbgm 459 | koennvmolejeftij 460 | rvzlreqikqlgyczj 461 | xrnujfoyhonzkdgd 462 | mmsmhkxaiqupfjil 463 | ypjwoemqizddvyfd 464 | qgugcxnbhvgahykj 465 | cviodlsrtimbkgmy 466 | xbfbbechhmrjxhnw 467 | psuipaoucfczfxkp 468 | hdhwcpeuptgqqvim 469 | gsxlruhjeaareilr 470 | vgyqonnljuznyrhk 471 | eewezahlumervpyu 472 | iiolebrxfadtnigy 473 | tdadlrodykrdfscn 474 | ocvdtzjxrhtjurpo 475 | gidljbuvuovkhhrf 476 | qwfcpilbjwzboohd 477 | xzohxonlezuiupbg 478 | vslpbkkqgvgbcbix 479 | pivzqrzfxosbstzn 480 | fyqcfboevcqmbhhs 481 | yqsrneacnlxswojx 482 | heicqpxxyrwcbsjz 483 | yzynmnnoumkmlbeh 484 | bncadbjdvvmczylw 485 | hlnjskgfzbgmigfn 486 | fphpszymugpcykka 487 | zbifcktanxpmufvy 488 | saklpkhoyfeqbguy 489 | nqtqfcfxmpivnjyo 490 | locygrwerxlsvzqm 491 | qqflecydqvlogjme 492 | njklmixvgkzpgppf 493 | ugzkpjwjflaswyma 494 | lriousvkbeftslcy 495 | nsvsauxzfbbotgmh 496 | tblcpuhjyybrlica 497 | hqwshxcilwtmxrsf 498 | xojwroydfeoqupup 499 | tikuzsrogpnohpib 500 | layenyqgxdfggloc 501 | nqsvjvbrpuxkqvmq 502 | ivchgxkdlfjdzxmk 503 | uoghiuosiiwiwdws 504 | twsgsfzyszsfinlc 505 | waixcmadmhtqvcmd 506 | zkgitozgrqehtjkw 507 | xbkmyxkzqyktmpfi 508 | qlyapfmlybmatwxn 509 | ntawlvcpuaebuypf 510 | clhebxqdkcyndyof 511 | nrcxuceywiklpemc 512 | lmurgiminxpapzmq 513 | obalwqlkykzflxou 514 | huvcudpiryefbcye 515 | zlxbddpnyuyapach 516 | gqfwzfislmwzyegy 517 | jhynkjtxedmemlob 518 | hmrnvjodnsfiukex 519 | pstmikjykzyavfef 520 | wuwpnscrwzsyalyt 521 | hksvadripgdgwynm 522 | tvpfthzjleqfxwkh 523 | xpmrxxepkrosnrco 524 | qjkqecsnevlhqsly 525 | jjnrfsxzzwkhnwdm 526 | pehmzrzsjngccale 527 | bsnansnfxduritrr 528 | ejzxkefwmzmbxhlb 529 | pceatehnizeujfrs 530 | jtidrtgxopyeslzl 531 | sytaoidnamfwtqcr 532 | iabjnikomkgmyirr 533 | eitavndozoezojsi 534 | wtsbhaftgrbqfsmm 535 | vvusvrivsmhtfild 536 | qifbtzszfyzsjzyx 537 | ifhhjpaqatpbxzau 538 | etjqdimpyjxiuhty 539 | fvllmbdbsjozxrip 540 | tjtgkadqkdtdlkpi 541 | xnydmjleowezrecn 542 | vhcbhxqalroaryfn 543 | scgvfqsangfbhtay 544 | lbufpduxwvdkwhmb 545 | tshipehzspkhmdoi 546 | gtszsebsulyajcfl 547 | dlrzswhxajcivlgg 548 | kgjruggcikrfrkrw 549 | xxupctxtmryersbn 550 | hljjqfjrubzozxts 551 | giaxjhcwazrenjzs 552 | tyffxtpufpxylpye 553 | jfugdxxyfwkzqmgv 554 | kbgufbosjghahacw 555 | xpbhhssgegmthwxb 556 | npefofiharjypyzk 557 | velxsseyxuhrpycy 558 | sglslryxsiwwqzfw 559 | susohnlpelojhklv 560 | lfnpqfvptqhogdmk 561 | vtcrzetlekguqyle 562 | jlyggqdtamcjiuxn 563 | olxxqfgizjmvigvl 564 | cyypypveppxxxfuq 565 | hewmxtlzfqoqznwd 566 | jzgxxybfeqfyzsmp 567 | xzvvndrhuejnzesx 568 | esiripjpvtqqwjkv 569 | xnhrwhjtactofwrd 570 | knuzpuogbzplofqx 571 | tihycsdwqggxntqk 572 | xkfywvvugkdalehs 573 | cztwdivxagtqjjel 574 | dsaslcagopsbfioy 575 | gmowqtkgrlqjimbl 576 | ctcomvdbiatdvbsd 577 | gujyrnpsssxmqjhz 578 | nygeovliqjfauhjf 579 | mmgmcvnuppkbnonz 580 | bhipnkoxhzcotwel 581 | wkwpgedgxvpltqid 582 | mliajvpdocyzcbot 583 | kqjhsipuibyjuref 584 | zqdczykothbgxwsy 585 | koirtljkuqzxioaz 586 | audpjvhmqzvhzqas 587 | cxyhxlhntyidldfx 588 | iasgocejboxjgtkx 589 | abehujmqotwcufxp 590 | fmlrzqmazajxeedl 591 | knswpkekbacuxfby 592 | yvyalnvrxgstqhxm 593 | sjnrljfrfuyqfwuw 594 | ssaqruwarlvxrqzm 595 | iaxbpeqqzlcwfqjz 596 | uwyxshjutkanvvsc 597 | uxwrlwbblcianvnb 598 | nodtifgrxdojhneh 599 | mloxjfusriktxrms 600 | lkfzrwulbctupggc 601 | gcrjljatfhitcgfj 602 | tkdfxeanwskaivqs 603 | ypyjxqtmitwubbgt 604 | ssxbygzbjsltedjj 605 | zdrsnoorwqfalnha 606 | xlgmissaiqmowppd 607 | azhbwhiopwpguiuo 608 | fydlahgxtekbweet 609 | qtaveuqpifprdoiy 610 | kpubqyepxqleucem 611 | wlqrgqmnupwiuory 612 | rwyocktuqkuhdwxz 613 | abzjfsdevoygctqv 614 | zsofhaqqghncmzuw 615 | lqbjwjqxqbfgdckc 616 | bkhyxjkrqbbunido 617 | yepxfjnnhldidsjb 618 | builayfduxbppafc 619 | wedllowzeuswkuez 620 | gverfowxwtnvgrmo 621 | tpxycfumxdqgntwf 622 | lqzokaoglwnfcolw 623 | yqsksyheyspmcdqt 624 | vufvchcjjcltwddl 625 | saeatqmuvnoacddt 626 | dxjngeydvsjbobjs 627 | ucrcxoakevhsgcep 628 | cajgwjsfxkasbayt 629 | hknzmteafsfemwuv 630 | xxwhxwiinchqqudr 631 | usfenmavvuevevgr 632 | kxcobcwhsgyizjok 633 | vhqnydeboeunnvyk 634 | bgxbwbxypnxvaacw 635 | bwjzdypacwgervgk 636 | rrioqjluawwwnjcr 637 | fiaeyggmgijnasot 638 | xizotjsoqmkvhbzm 639 | uzphtrpxwfnaiidz 640 | kihppzgvgyoncptg 641 | hfbkfrxwejdeuwbz 642 | zgqthtuaqyrxicdy 643 | zitqdjnnwhznftze 644 | jnzlplsrwovxlqsn 645 | bmwrobuhwnwivpca 646 | uuwsvcdnoyovxuhn 647 | nmfvoqgoppoyosaj 648 | hxjkcppaisezygpe 649 | icvnysgixapvtoos 650 | vbvzajjgrmjygkhu 651 | jinptbqkyqredaos 652 | dpmknzhkhleawfvz 653 | ouwwkfhcedsgqqxe 654 | owroouiyptrijzgv 655 | bewnckpmnbrmhfyu 656 | evdqxevdacsbfbjb 657 | catppmrovqavxstn 658 | dqsbjibugjkhgazg 659 | mkcldhjochtnvvne 660 | sblkmhtifwtfnmsx 661 | lynnaujghehmpfpt 662 | vrseaozoheawffoq 663 | ytysdzbpbazorqes 664 | sezawbudymfvziff 665 | vrlfhledogbgxbau 666 | bipdlplesdezbldn 667 | ermaenjunjtbekeo 668 | eyaedubkthdecxjq 669 | gbzurepoojlwucuy 670 | rsiaqiiipjlouecx 671 | beqjhvroixhiemtw 672 | buzlowghhqbcbdwv 673 | ldexambveeosaimo 674 | fpyjzachgrhxcvnx 675 | komgvqejojpnykol 676 | fxebehjoxdujwmfu 677 | jnfgvheocgtvmvkx 678 | qmcclxxgnclkuspx 679 | rsbelzrfdblatmzu 680 | vexzwqjqrsenlrhm 681 | tnfbkclwetommqmh 682 | lzoskleonvmprdri 683 | nnahplxqscvtgfwi 684 | ubqdsflhnmiayzrp 685 | xtiyqxhfyqonqzrn 686 | omdtmjeqhmlfojfr 687 | cnimgkdbxkkcnmkb 688 | tapyijgmxzbmqnks 689 | byacsxavjboovukk 690 | awugnhcrygaoppjq 691 | yxcnwrvhojpuxehg 692 | btjdudofhxmgqbao 693 | nzqlfygiysfuilou 694 | nubwfjdxavunrliq 695 | vqxmmhsbmhlewceh 696 | ygavmcybepzfevrp 697 | kgflmrqsvxprkqgq 698 | iaqyqmcaedscmakk 699 | cvbojnbfmrawxzkh 700 | jjjrprbnlijzatuw 701 | lcsudrrfnnggbrmk 702 | qzgxbiavunawfibc 703 | gnnalgfvefdfdwwg 704 | nokmiitzrigxavsc 705 | etzoxwzxqkkhvais 706 | urxxfacgjccieufi 707 | lqrioqhuvgcotuec 708 | dydbaeyoypsbftra 709 | hhrotenctylggzaf 710 | evctqvzjnozpdxzu 711 | tbpvithmorujxlcp 712 | pllbtcbrtkfpvxcw 713 | fzyxdqilyvqreowv 714 | xdleeddxwvqjfmmt 715 | fcldzthqqpbswoin 716 | sgomzrpjfmvgwlzi 717 | axjyskmtdjbxpwoz 718 | hcvaevqxsmabvswh 719 | lfdlsfcwkwicizfk 720 | isjbwpzdognhoxvm 721 | oqnexibqxlyxpluh 722 | zqfbgodsfzwgcwuf 723 | kvmnwruwsjllbldz 724 | kghazimdyiyhmokj 725 | uiktgpsxpoahofxn 726 | zkdwawxargcmidct 727 | ftbixlyiprshrjup 728 | nofhmbxififwroeg 729 | mcdaqrhplffxrcdt 730 | fbjxnwojcvlawmlb 731 | rizoftvwfdhiwyac 732 | eduogrtyhxfwyars 733 | zoikunqxgjwfqqwr 734 | zxwbbpmvctzezaqh 735 | nghujwyeabwdqnop 736 | vcxamijpoyyksogn 737 | jnckdbuteoqlsdae 738 | jurfqqawafmsiqwv 739 | inepmztrzehfafie 740 | tznzkyvzodbrtscf 741 | xewbavjeppflwscl 742 | ucndzsorexjlnplo 743 | jpxbctscngxgusvu 744 | mfmygcllauzuoaok 745 | oibkuxhjmhxhhzby 746 | zjkslwagmeoisunw 747 | avnnxmopdgvmukuu 748 | jmaargejcwboqhkt 749 | yacmpeosarsrfkrv 750 | iqhgupookcaovwgh 751 | ebjkdnxwtikqzufc 752 | imdhbarytcscbsvb 753 | ifyibukeffkbqvcr 754 | aloighmyvwybtxhx 755 | yszqwrutbkiwkxjg 756 | xyholyzlltjhsuhp 757 | gykhmrwucneoxcrf 758 | badkdgqrpjzbabet 759 | sunaucaucykwtkjj 760 | pumqkglgfdhneero 761 | usgtyuestahlydxq 762 | xmfhflphzeudjsjm 763 | knywgmclisgpootg 764 | mtojnyrnvxtweuzb 765 | uuxufbwfegysabww 766 | vobhwwocqttlbsik 767 | yuydfezeqgqxqmnd 768 | wbqgqkwbibiilhzc 769 | sfdmgxsbuzsawush 770 | ilhbxcfgordyxwvp 771 | ahqoavuysblnqaeg 772 | plwgtvpgotskmsey 773 | ewjcmzkcnautrrmp 774 | tyekgzbznlikcyqj 775 | bqzctiuaxpriuiga 776 | bimvbfjkiupyqiys 777 | mpqtbcxfhwymxncw 778 | htemlptvqhharjgb 779 | mqbsmsruwzzxgcxc 780 | zjyedjwhnvteuaid 781 | pzoelkoidwglpttc 782 | efydnsvlfimvwxhx 783 | gfyhgoeiyjcgfyze 784 | deqtomhwopmzvjlt 785 | casafubtkoopuaju 786 | yylsfarntbucfulg 787 | mgjwsormkjsrrxan 788 | lkkenpupgmjpnqqd 789 | tegweszyohsoluot 790 | lihsfdwxmxvwdxna 791 | rrefrjjxerphejwb 792 | guuazonjoebhymtm 793 | ysofqzmfmyneziki 794 | lmjgaliatcpduoal 795 | qzthcpjwtgahbebr 796 | wvakvephyukmpemm 797 | simxacxxzfoaeddw 798 | aetgqmiqzxbvbviz 799 | jxlmhdmqggevrxes 800 | mmuglnjmuddzgaik 801 | svopsqhtrslgycgc 802 | xnvcsiiqrcjkvecn 803 | kkvumxtvashxcops 804 | bduflsdyeectvcgl 805 | vfrxbwmmytjvqnsj 806 | eeqtdneiyiaiofxw 807 | crtbgknfacjtwkfl 808 | uuutuoxdsxolpbhd 809 | lcrztwzreaswovtn 810 | htorkvnvujmjdqzj 811 | wttzuzvrzlyhfzyf 812 | oraewznfwgdsnhuk 813 | rctlkqqvkwbgrcgk 814 | cfehrsrqhzyiwtmz 815 | kbvxwcumjkhvjpui 816 | xxlocexbmniiakfo 817 | gtknkkzvykmlqghl 818 | kcjuxvkuimhwqrtk 819 | vohekwkuyuoacuww 820 | vorctgughscysyfo 821 | zmjevqplngzswxyq 822 | qhswdrhrijnatkyo 823 | joakcwpfggtitizs 824 | juzlwjijcmtswdtq 825 | icbyaqohpkemhkip 826 | rpdxgpzxncedmvzh 827 | rozkmimbqhbhcddv 828 | wkkypomlvyglpfpf 829 | jcaqyaqvsefwtaya 830 | ghvmtecoxlebdwnf 831 | lqrcyiykkkpkxvqt 832 | eqlarfazchmzotev 833 | vqwndafvmpguggef 834 | dbfxzrdkkrusmdke 835 | cmjpjjgndozcmefj 836 | hbrdcwjuyxapyhlo 837 | mmforetykbosdwce 838 | zynfntqwblbnfqik 839 | sodwujfwlasznaiz 840 | yyvrivjiqnxzqkfp 841 | uldbskmmjbqllpnm 842 | fyhhrmrsukeptynl 843 | hpfjekktvdkgdkzl 844 | bozhkoekcxzeorob 845 | uvpptyfrzkvmtoky 846 | hkhfprmjdpjvfkcb 847 | igxzwktwsqhsivqu 848 | qceomwysgkcylipb 849 | cglateoynluyeqgc 850 | xcsdfkpeguxgvpfh 851 | owjhxlcncdgkqyia 852 | rpbmrpcesiakqpna 853 | lueszxiourxsmezb 854 | zelvsowimzkxliwc 855 | vzxbttoobtvdtkca 856 | pfxvzphzwscqkzsi 857 | edsjorainowytbzu 858 | ipsegdaluoiphmnz 859 | mkhueokfpemywvuw 860 | urxdnumhylpafdlc 861 | ggluurzavsxkvwkl 862 | ctclphidqgteakox 863 | tfobosynxsktajuk 864 | jzrmemhxqmzhllif 865 | eemwekimdfvqslsx 866 | yjkwpzrbanoaajgq 867 | rlxghzanuyeimfhx 868 | hozbgdoorhthlqpv 869 | obkbmflhyanxilnx 870 | xojrippyxjmpzmsz 871 | ukykmbfheixuviue 872 | qivlmdexwucqkres 873 | rmyxxipqkarpjmox 874 | fgaftctbvcvnrror 875 | raawxozucfqvasru 876 | dinpjbdfjfizexdh 877 | gybxubwnnbuyvjcr 878 | qrqitdvyoneqyxcg 879 | jqzcfggayzyoqteo 880 | cikqpvxizpdbmppm 881 | stfpldgyhfmucjjv 882 | slzbcuihmimpduri 883 | aufajwfrsorqqsnl 884 | iylmzraibygmgmqj 885 | lcdyfpcqlktudfmu 886 | pmomzzsdpvgkkliw 887 | zpplirgtscfhbrkj 888 | mvhyerxfiljlotjl 889 | ofkvrorwwhusyxjx 890 | xngzmvcgkqfltjpe 891 | yxfxaqipmysahqqq 892 | sdqafdzgfdjuabup 893 | qcqajmerahcdgxfv 894 | xqimrqtupbapawro 895 | qfvkqwidzzrehsbl 896 | himixxvueksiqfdf 897 | vgtfqpuzxxmhrvvd 898 | adiioqeiejguaost 899 | jnzxuycjxvxehbvm 900 | xedbpxdhphamoodk 901 | jsrioscmwlsfuxrg 902 | mtsynnfxunuohbnf 903 | enamqzfzjunnnkpe 904 | uwcvfecunobyhces 905 | ciygixtgbsccpftq 906 | ewjgcronizkcsfjy 907 | wztjkoipxsikoimv 908 | jrgalyvfelwxforw 909 | imylyalawbqwkrwb 910 | yflwqfnuuvgjsgcj 911 | wkysyzusldlojoue 912 | zopllxnidcffcuau 913 | bscgwxuprxaerskj 914 | zvnvprxxjkhnkkpq 915 | nejwxbhjxxdbenid 916 | chryiccsebdbcnkc 917 | guoeefaeafhlgvxh 918 | nzapxrfrrqhsingx 919 | mkzvquzvqvwsejqs 920 | kozmlmbchydtxeeo 921 | keylygnoqhmfzrfp 922 | srwzoxccndoxylxe 923 | uqjzalppoorosxxo 924 | potmkinyuqxsfdfw 925 | qkkwrhpbhypxhiun 926 | wgfvnogarjmdbxyh 927 | gkidtvepcvxopzuf 928 | atwhvmmdvmewhzty 929 | pybxizvuiwwngqej 930 | zfumwnazxwwxtiry 931 | keboraqttctosemx 932 | vtlzxaqdetbhclib 933 | wjiecykptzexuayl 934 | ejatfnyjjdawepyk 935 | mpcrobansyssvmju 936 | gqukndzganeueabm 937 | ukzscvomorucdnqd 938 | wfydhtbzehgwfazx 939 | mtwqdzlephqvxqmx 940 | dltmlfxbjopefibh 941 | atcfrowdflluqtbi 942 | vowawlophlxaqonw 943 | vblgdjzvwnocdipw 944 | uzerzksmkvnlvlhm 945 | ytjwhpaylohorvxd 946 | siprvfxvnxcdgofz 947 | cbhjupewcyjhvtgs 948 | apqtozaofusmfqli 949 | tmssrtlxfouowqnr 950 | ntutrvwnzzgmokes 951 | zrsgpwdzokztdpis 952 | nrobvmsxtfmrqdhv 953 | kadkaftffaziqdze 954 | yrovbgcyqtlsnoux 955 | modheiwuhntdecqs 956 | gzhjypwddizemnys 957 | gaputpwpcsvzxjho 958 | bgmouxwoajgaozau 959 | oxuapfrjcpyakiwt 960 | kntwbvhuaahdixzj 961 | epqjdjbnkxdnaccx 962 | dspltdvznhypykri 963 | tdrgqmbnagrxdwtt 964 | njfqawzjggmemtbg 965 | chpemsgwpzjpdnkk 966 | fpsrobmbqbmigmwk 967 | flxptsrqaazmprnl 968 | nzdunrxlcbfklshm 969 | miuwljvtkgzdlbnn 970 | xbhjakklmbhsdmdt 971 | xwxhsbnrwnegwcov 972 | pwosflhodjaiexwq 973 | fhgepuluczttfvqh 974 | tldxcacbvxyamvkt 975 | gffxatrjglkcehim 976 | tzotkdrpxkucsdps 977 | wxheftdepysvmzbe 978 | qfooyczdzoewrmku 979 | rvlwikuqdbpjuvoo 980 | bcbrnbtfrdgijtzt 981 | vaxqmvuogsxonlgq 982 | ibsolflngegravgo 983 | txntccjmqakcoorp 984 | vrrbmqaxfbarmlmc 985 | dzspqmttgsuhczto 986 | pikcscjunxlwqtiw 987 | lwzyogwxqitqfqlv 988 | gsgjsuaqejtzglym 989 | feyeqguxbgmcmgpp 990 | gmttebyebdwvprkn 991 | mzuuwbhzdjfdryxu 992 | fganrbnplymqbzjx 993 | cvsrbdcvhtxxdmro 994 | scmgkjlkqukoamyp 995 | fkgrqbyqpqcworqc 996 | hjsrvkdibdjarxxb 997 | sztzziuqroeidcus 998 | pxdfvcpvwaddrzwv 999 | phdqqxleqdjfgfbg 1000 | cqfikbgxvjmnfncy 1001 | -------------------------------------------------------------------------------- /input6.txt: -------------------------------------------------------------------------------- 1 | turn on 887,9 through 959,629 2 | turn on 454,398 through 844,448 3 | turn off 539,243 through 559,965 4 | turn off 370,819 through 676,868 5 | turn off 145,40 through 370,997 6 | turn off 301,3 through 808,453 7 | turn on 351,678 through 951,908 8 | toggle 720,196 through 897,994 9 | toggle 831,394 through 904,860 10 | toggle 753,664 through 970,926 11 | turn off 150,300 through 213,740 12 | turn on 141,242 through 932,871 13 | toggle 294,259 through 474,326 14 | toggle 678,333 through 752,957 15 | toggle 393,804 through 510,976 16 | turn off 6,964 through 411,976 17 | turn off 33,572 through 978,590 18 | turn on 579,693 through 650,978 19 | turn on 150,20 through 652,719 20 | turn off 782,143 through 808,802 21 | turn off 240,377 through 761,468 22 | turn off 899,828 through 958,967 23 | turn on 613,565 through 952,659 24 | turn on 295,36 through 964,978 25 | toggle 846,296 through 969,528 26 | turn off 211,254 through 529,491 27 | turn off 231,594 through 406,794 28 | turn off 169,791 through 758,942 29 | turn on 955,440 through 980,477 30 | toggle 944,498 through 995,928 31 | turn on 519,391 through 605,718 32 | toggle 521,303 through 617,366 33 | turn off 524,349 through 694,791 34 | toggle 391,87 through 499,792 35 | toggle 562,527 through 668,935 36 | turn off 68,358 through 857,453 37 | toggle 815,811 through 889,828 38 | turn off 666,61 through 768,87 39 | turn on 27,501 through 921,952 40 | turn on 953,102 through 983,471 41 | turn on 277,552 through 451,723 42 | turn off 64,253 through 655,960 43 | turn on 47,485 through 734,977 44 | turn off 59,119 through 699,734 45 | toggle 407,898 through 493,955 46 | toggle 912,966 through 949,991 47 | turn on 479,990 through 895,990 48 | toggle 390,589 through 869,766 49 | toggle 593,903 through 926,943 50 | toggle 358,439 through 870,528 51 | turn off 649,410 through 652,875 52 | turn on 629,834 through 712,895 53 | toggle 254,555 through 770,901 54 | toggle 641,832 through 947,850 55 | turn on 268,448 through 743,777 56 | turn off 512,123 through 625,874 57 | turn off 498,262 through 930,811 58 | turn off 835,158 through 886,242 59 | toggle 546,310 through 607,773 60 | turn on 501,505 through 896,909 61 | turn off 666,796 through 817,924 62 | toggle 987,789 through 993,809 63 | toggle 745,8 through 860,693 64 | toggle 181,983 through 731,988 65 | turn on 826,174 through 924,883 66 | turn on 239,228 through 843,993 67 | turn on 205,613 through 891,667 68 | toggle 867,873 through 984,896 69 | turn on 628,251 through 677,681 70 | toggle 276,956 through 631,964 71 | turn on 78,358 through 974,713 72 | turn on 521,360 through 773,597 73 | turn off 963,52 through 979,502 74 | turn on 117,151 through 934,622 75 | toggle 237,91 through 528,164 76 | turn on 944,269 through 975,453 77 | toggle 979,460 through 988,964 78 | turn off 440,254 through 681,507 79 | toggle 347,100 through 896,785 80 | turn off 329,592 through 369,985 81 | turn on 931,960 through 979,985 82 | toggle 703,3 through 776,36 83 | toggle 798,120 through 908,550 84 | turn off 186,605 through 914,709 85 | turn off 921,725 through 979,956 86 | toggle 167,34 through 735,249 87 | turn on 726,781 through 987,936 88 | toggle 720,336 through 847,756 89 | turn on 171,630 through 656,769 90 | turn off 417,276 through 751,500 91 | toggle 559,485 through 584,534 92 | turn on 568,629 through 690,873 93 | toggle 248,712 through 277,988 94 | toggle 345,594 through 812,723 95 | turn off 800,108 through 834,618 96 | turn off 967,439 through 986,869 97 | turn on 842,209 through 955,529 98 | turn on 132,653 through 357,696 99 | turn on 817,38 through 973,662 100 | turn off 569,816 through 721,861 101 | turn on 568,429 through 945,724 102 | turn on 77,458 through 844,685 103 | turn off 138,78 through 498,851 104 | turn on 136,21 through 252,986 105 | turn off 2,460 through 863,472 106 | turn on 172,81 through 839,332 107 | turn on 123,216 through 703,384 108 | turn off 879,644 through 944,887 109 | toggle 227,491 through 504,793 110 | toggle 580,418 through 741,479 111 | toggle 65,276 through 414,299 112 | toggle 482,486 through 838,931 113 | turn off 557,768 through 950,927 114 | turn off 615,617 through 955,864 115 | turn on 859,886 through 923,919 116 | turn on 391,330 through 499,971 117 | toggle 521,835 through 613,847 118 | turn on 822,787 through 989,847 119 | turn on 192,142 through 357,846 120 | turn off 564,945 through 985,945 121 | turn off 479,361 through 703,799 122 | toggle 56,481 through 489,978 123 | turn off 632,991 through 774,998 124 | toggle 723,526 through 945,792 125 | turn on 344,149 through 441,640 126 | toggle 568,927 through 624,952 127 | turn on 621,784 through 970,788 128 | toggle 665,783 through 795,981 129 | toggle 386,610 through 817,730 130 | toggle 440,399 through 734,417 131 | toggle 939,201 through 978,803 132 | turn off 395,883 through 554,929 133 | turn on 340,309 through 637,561 134 | turn off 875,147 through 946,481 135 | turn off 945,837 through 957,922 136 | turn off 429,982 through 691,991 137 | toggle 227,137 through 439,822 138 | toggle 4,848 through 7,932 139 | turn off 545,146 through 756,943 140 | turn on 763,863 through 937,994 141 | turn on 232,94 through 404,502 142 | turn off 742,254 through 930,512 143 | turn on 91,931 through 101,942 144 | toggle 585,106 through 651,425 145 | turn on 506,700 through 567,960 146 | turn off 548,44 through 718,352 147 | turn off 194,827 through 673,859 148 | turn off 6,645 through 509,764 149 | turn off 13,230 through 821,361 150 | turn on 734,629 through 919,631 151 | toggle 788,552 through 957,972 152 | toggle 244,747 through 849,773 153 | turn off 162,553 through 276,887 154 | turn off 569,577 through 587,604 155 | turn off 799,482 through 854,956 156 | turn on 744,535 through 909,802 157 | toggle 330,641 through 396,986 158 | turn off 927,458 through 966,564 159 | toggle 984,486 through 986,913 160 | toggle 519,682 through 632,708 161 | turn on 984,977 through 989,986 162 | toggle 766,423 through 934,495 163 | turn on 17,509 through 947,718 164 | turn on 413,783 through 631,903 165 | turn on 482,370 through 493,688 166 | turn on 433,859 through 628,938 167 | turn off 769,549 through 945,810 168 | turn on 178,853 through 539,941 169 | turn off 203,251 through 692,433 170 | turn off 525,638 through 955,794 171 | turn on 169,70 through 764,939 172 | toggle 59,352 through 896,404 173 | toggle 143,245 through 707,320 174 | turn off 103,35 through 160,949 175 | toggle 496,24 through 669,507 176 | turn off 581,847 through 847,903 177 | turn on 689,153 through 733,562 178 | turn on 821,487 through 839,699 179 | turn on 837,627 through 978,723 180 | toggle 96,748 through 973,753 181 | toggle 99,818 through 609,995 182 | turn on 731,193 through 756,509 183 | turn off 622,55 through 813,365 184 | turn on 456,490 through 576,548 185 | turn on 48,421 through 163,674 186 | turn off 853,861 through 924,964 187 | turn off 59,963 through 556,987 188 | turn on 458,710 through 688,847 189 | toggle 12,484 through 878,562 190 | turn off 241,964 through 799,983 191 | turn off 434,299 through 845,772 192 | toggle 896,725 through 956,847 193 | turn on 740,289 through 784,345 194 | turn off 395,840 through 822,845 195 | turn on 955,224 through 996,953 196 | turn off 710,186 through 957,722 197 | turn off 485,949 through 869,985 198 | turn on 848,209 through 975,376 199 | toggle 221,241 through 906,384 200 | turn on 588,49 through 927,496 201 | turn on 273,332 through 735,725 202 | turn on 505,962 through 895,962 203 | toggle 820,112 through 923,143 204 | turn on 919,792 through 978,982 205 | toggle 489,461 through 910,737 206 | turn off 202,642 through 638,940 207 | turn off 708,953 through 970,960 208 | toggle 437,291 through 546,381 209 | turn on 409,358 through 837,479 210 | turn off 756,279 through 870,943 211 | turn off 154,657 through 375,703 212 | turn off 524,622 through 995,779 213 | toggle 514,221 through 651,850 214 | toggle 808,464 through 886,646 215 | toggle 483,537 through 739,840 216 | toggle 654,769 through 831,825 217 | turn off 326,37 through 631,69 218 | turn off 590,570 through 926,656 219 | turn off 881,913 through 911,998 220 | turn on 996,102 through 998,616 221 | turn off 677,503 through 828,563 222 | turn on 860,251 through 877,441 223 | turn off 964,100 through 982,377 224 | toggle 888,403 through 961,597 225 | turn off 632,240 through 938,968 226 | toggle 731,176 through 932,413 227 | turn on 5,498 through 203,835 228 | turn on 819,352 through 929,855 229 | toggle 393,813 through 832,816 230 | toggle 725,689 through 967,888 231 | turn on 968,950 through 969,983 232 | turn off 152,628 through 582,896 233 | turn off 165,844 through 459,935 234 | turn off 882,741 through 974,786 235 | turn off 283,179 through 731,899 236 | toggle 197,366 through 682,445 237 | turn on 106,309 through 120,813 238 | toggle 950,387 through 967,782 239 | turn off 274,603 through 383,759 240 | turn off 155,665 through 284,787 241 | toggle 551,871 through 860,962 242 | turn off 30,826 through 598,892 243 | toggle 76,552 through 977,888 244 | turn on 938,180 through 994,997 245 | toggle 62,381 through 993,656 246 | toggle 625,861 through 921,941 247 | turn on 685,311 through 872,521 248 | turn on 124,934 through 530,962 249 | turn on 606,379 through 961,867 250 | turn off 792,735 through 946,783 251 | turn on 417,480 through 860,598 252 | toggle 178,91 through 481,887 253 | turn off 23,935 through 833,962 254 | toggle 317,14 through 793,425 255 | turn on 986,89 through 999,613 256 | turn off 359,201 through 560,554 257 | turn off 729,494 through 942,626 258 | turn on 204,143 through 876,610 259 | toggle 474,97 through 636,542 260 | turn off 902,924 through 976,973 261 | turn off 389,442 through 824,638 262 | turn off 622,863 through 798,863 263 | turn on 840,622 through 978,920 264 | toggle 567,374 through 925,439 265 | turn off 643,319 through 935,662 266 | toggle 185,42 through 294,810 267 | turn on 47,124 through 598,880 268 | toggle 828,303 through 979,770 269 | turn off 174,272 through 280,311 270 | turn off 540,50 through 880,212 271 | turn on 141,994 through 221,998 272 | turn on 476,695 through 483,901 273 | turn on 960,216 through 972,502 274 | toggle 752,335 through 957,733 275 | turn off 419,713 through 537,998 276 | toggle 772,846 through 994,888 277 | turn on 881,159 through 902,312 278 | turn off 537,651 through 641,816 279 | toggle 561,947 through 638,965 280 | turn on 368,458 through 437,612 281 | turn on 290,149 through 705,919 282 | turn on 711,918 through 974,945 283 | toggle 916,242 through 926,786 284 | toggle 522,272 through 773,314 285 | turn on 432,897 through 440,954 286 | turn off 132,169 through 775,380 287 | toggle 52,205 through 693,747 288 | toggle 926,309 through 976,669 289 | turn off 838,342 through 938,444 290 | turn on 144,431 through 260,951 291 | toggle 780,318 through 975,495 292 | turn off 185,412 through 796,541 293 | turn on 879,548 through 892,860 294 | turn on 294,132 through 460,338 295 | turn on 823,500 through 899,529 296 | turn off 225,603 through 483,920 297 | toggle 717,493 through 930,875 298 | toggle 534,948 through 599,968 299 | turn on 522,730 through 968,950 300 | turn off 102,229 through 674,529 301 | -------------------------------------------------------------------------------- /input7.txt: -------------------------------------------------------------------------------- 1 | lf AND lq -> ls 2 | iu RSHIFT 1 -> jn 3 | bo OR bu -> bv 4 | gj RSHIFT 1 -> hc 5 | et RSHIFT 2 -> eu 6 | bv AND bx -> by 7 | is OR it -> iu 8 | b OR n -> o 9 | gf OR ge -> gg 10 | NOT kt -> ku 11 | ea AND eb -> ed 12 | kl OR kr -> ks 13 | hi AND hk -> hl 14 | au AND av -> ax 15 | lf RSHIFT 2 -> lg 16 | dd RSHIFT 3 -> df 17 | eu AND fa -> fc 18 | df AND dg -> di 19 | ip LSHIFT 15 -> it 20 | NOT el -> em 21 | et OR fe -> ff 22 | fj LSHIFT 15 -> fn 23 | t OR s -> u 24 | ly OR lz -> ma 25 | ko AND kq -> kr 26 | NOT fx -> fy 27 | et RSHIFT 1 -> fm 28 | eu OR fa -> fb 29 | dd RSHIFT 2 -> de 30 | NOT go -> gp 31 | kb AND kd -> ke 32 | hg OR hh -> hi 33 | jm LSHIFT 1 -> kg 34 | NOT cn -> co 35 | jp RSHIFT 2 -> jq 36 | jp RSHIFT 5 -> js 37 | 1 AND io -> ip 38 | eo LSHIFT 15 -> es 39 | 1 AND jj -> jk 40 | g AND i -> j 41 | ci RSHIFT 3 -> ck 42 | gn AND gp -> gq 43 | fs AND fu -> fv 44 | lj AND ll -> lm 45 | jk LSHIFT 15 -> jo 46 | iu RSHIFT 3 -> iw 47 | NOT ii -> ij 48 | 1 AND cc -> cd 49 | bn RSHIFT 3 -> bp 50 | NOT gw -> gx 51 | NOT ft -> fu 52 | jn OR jo -> jp 53 | iv OR jb -> jc 54 | hv OR hu -> hw 55 | 19138 -> b 56 | gj RSHIFT 5 -> gm 57 | hq AND hs -> ht 58 | dy RSHIFT 1 -> er 59 | ao OR an -> ap 60 | ld OR le -> lf 61 | bk LSHIFT 1 -> ce 62 | bz AND cb -> cc 63 | bi LSHIFT 15 -> bm 64 | il AND in -> io 65 | af AND ah -> ai 66 | as RSHIFT 1 -> bl 67 | lf RSHIFT 3 -> lh 68 | er OR es -> et 69 | NOT ax -> ay 70 | ci RSHIFT 1 -> db 71 | et AND fe -> fg 72 | lg OR lm -> ln 73 | k AND m -> n 74 | hz RSHIFT 2 -> ia 75 | kh LSHIFT 1 -> lb 76 | NOT ey -> ez 77 | NOT di -> dj 78 | dz OR ef -> eg 79 | lx -> a 80 | NOT iz -> ja 81 | gz LSHIFT 15 -> hd 82 | ce OR cd -> cf 83 | fq AND fr -> ft 84 | at AND az -> bb 85 | ha OR gz -> hb 86 | fp AND fv -> fx 87 | NOT gb -> gc 88 | ia AND ig -> ii 89 | gl OR gm -> gn 90 | 0 -> c 91 | NOT ca -> cb 92 | bn RSHIFT 1 -> cg 93 | c LSHIFT 1 -> t 94 | iw OR ix -> iy 95 | kg OR kf -> kh 96 | dy OR ej -> ek 97 | km AND kn -> kp 98 | NOT fc -> fd 99 | hz RSHIFT 3 -> ib 100 | NOT dq -> dr 101 | NOT fg -> fh 102 | dy RSHIFT 2 -> dz 103 | kk RSHIFT 2 -> kl 104 | 1 AND fi -> fj 105 | NOT hr -> hs 106 | jp RSHIFT 1 -> ki 107 | bl OR bm -> bn 108 | 1 AND gy -> gz 109 | gr AND gt -> gu 110 | db OR dc -> dd 111 | de OR dk -> dl 112 | as RSHIFT 5 -> av 113 | lf RSHIFT 5 -> li 114 | hm AND ho -> hp 115 | cg OR ch -> ci 116 | gj AND gu -> gw 117 | ge LSHIFT 15 -> gi 118 | e OR f -> g 119 | fp OR fv -> fw 120 | fb AND fd -> fe 121 | cd LSHIFT 15 -> ch 122 | b RSHIFT 1 -> v 123 | at OR az -> ba 124 | bn RSHIFT 2 -> bo 125 | lh AND li -> lk 126 | dl AND dn -> do 127 | eg AND ei -> ej 128 | ex AND ez -> fa 129 | NOT kp -> kq 130 | NOT lk -> ll 131 | x AND ai -> ak 132 | jp OR ka -> kb 133 | NOT jd -> je 134 | iy AND ja -> jb 135 | jp RSHIFT 3 -> jr 136 | fo OR fz -> ga 137 | df OR dg -> dh 138 | gj RSHIFT 2 -> gk 139 | gj OR gu -> gv 140 | NOT jh -> ji 141 | ap LSHIFT 1 -> bj 142 | NOT ls -> lt 143 | ir LSHIFT 1 -> jl 144 | bn AND by -> ca 145 | lv LSHIFT 15 -> lz 146 | ba AND bc -> bd 147 | cy LSHIFT 15 -> dc 148 | ln AND lp -> lq 149 | x RSHIFT 1 -> aq 150 | gk OR gq -> gr 151 | NOT kx -> ky 152 | jg AND ji -> jj 153 | bn OR by -> bz 154 | fl LSHIFT 1 -> gf 155 | bp OR bq -> br 156 | he OR hp -> hq 157 | et RSHIFT 5 -> ew 158 | iu RSHIFT 2 -> iv 159 | gl AND gm -> go 160 | x OR ai -> aj 161 | hc OR hd -> he 162 | lg AND lm -> lo 163 | lh OR li -> lj 164 | da LSHIFT 1 -> du 165 | fo RSHIFT 2 -> fp 166 | gk AND gq -> gs 167 | bj OR bi -> bk 168 | lf OR lq -> lr 169 | cj AND cp -> cr 170 | hu LSHIFT 15 -> hy 171 | 1 AND bh -> bi 172 | fo RSHIFT 3 -> fq 173 | NOT lo -> lp 174 | hw LSHIFT 1 -> iq 175 | dd RSHIFT 1 -> dw 176 | dt LSHIFT 15 -> dx 177 | dy AND ej -> el 178 | an LSHIFT 15 -> ar 179 | aq OR ar -> as 180 | 1 AND r -> s 181 | fw AND fy -> fz 182 | NOT im -> in 183 | et RSHIFT 3 -> ev 184 | 1 AND ds -> dt 185 | ec AND ee -> ef 186 | NOT ak -> al 187 | jl OR jk -> jm 188 | 1 AND en -> eo 189 | lb OR la -> lc 190 | iu AND jf -> jh 191 | iu RSHIFT 5 -> ix 192 | bo AND bu -> bw 193 | cz OR cy -> da 194 | iv AND jb -> jd 195 | iw AND ix -> iz 196 | lf RSHIFT 1 -> ly 197 | iu OR jf -> jg 198 | NOT dm -> dn 199 | lw OR lv -> lx 200 | gg LSHIFT 1 -> ha 201 | lr AND lt -> lu 202 | fm OR fn -> fo 203 | he RSHIFT 3 -> hg 204 | aj AND al -> am 205 | 1 AND kz -> la 206 | dy RSHIFT 5 -> eb 207 | jc AND je -> jf 208 | cm AND co -> cp 209 | gv AND gx -> gy 210 | ev OR ew -> ex 211 | jp AND ka -> kc 212 | fk OR fj -> fl 213 | dy RSHIFT 3 -> ea 214 | NOT bs -> bt 215 | NOT ag -> ah 216 | dz AND ef -> eh 217 | cf LSHIFT 1 -> cz 218 | NOT cv -> cw 219 | 1 AND cx -> cy 220 | de AND dk -> dm 221 | ck AND cl -> cn 222 | x RSHIFT 5 -> aa 223 | dv LSHIFT 1 -> ep 224 | he RSHIFT 2 -> hf 225 | NOT bw -> bx 226 | ck OR cl -> cm 227 | bp AND bq -> bs 228 | as OR bd -> be 229 | he AND hp -> hr 230 | ev AND ew -> ey 231 | 1 AND lu -> lv 232 | kk RSHIFT 3 -> km 233 | b AND n -> p 234 | NOT kc -> kd 235 | lc LSHIFT 1 -> lw 236 | km OR kn -> ko 237 | id AND if -> ig 238 | ih AND ij -> ik 239 | jr AND js -> ju 240 | ci RSHIFT 5 -> cl 241 | hz RSHIFT 1 -> is 242 | 1 AND ke -> kf 243 | NOT gs -> gt 244 | aw AND ay -> az 245 | x RSHIFT 2 -> y 246 | ab AND ad -> ae 247 | ff AND fh -> fi 248 | ci AND ct -> cv 249 | eq LSHIFT 1 -> fk 250 | gj RSHIFT 3 -> gl 251 | u LSHIFT 1 -> ao 252 | NOT bb -> bc 253 | NOT hj -> hk 254 | kw AND ky -> kz 255 | as AND bd -> bf 256 | dw OR dx -> dy 257 | br AND bt -> bu 258 | kk AND kv -> kx 259 | ep OR eo -> eq 260 | he RSHIFT 1 -> hx 261 | ki OR kj -> kk 262 | NOT ju -> jv 263 | ek AND em -> en 264 | kk RSHIFT 5 -> kn 265 | NOT eh -> ei 266 | hx OR hy -> hz 267 | ea OR eb -> ec 268 | s LSHIFT 15 -> w 269 | fo RSHIFT 1 -> gh 270 | kk OR kv -> kw 271 | bn RSHIFT 5 -> bq 272 | NOT ed -> ee 273 | 1 AND ht -> hu 274 | cu AND cw -> cx 275 | b RSHIFT 5 -> f 276 | kl AND kr -> kt 277 | iq OR ip -> ir 278 | ci RSHIFT 2 -> cj 279 | cj OR cp -> cq 280 | o AND q -> r 281 | dd RSHIFT 5 -> dg 282 | b RSHIFT 2 -> d 283 | ks AND ku -> kv 284 | b RSHIFT 3 -> e 285 | d OR j -> k 286 | NOT p -> q 287 | NOT cr -> cs 288 | du OR dt -> dv 289 | kf LSHIFT 15 -> kj 290 | NOT ac -> ad 291 | fo RSHIFT 5 -> fr 292 | hz OR ik -> il 293 | jx AND jz -> ka 294 | gh OR gi -> gj 295 | kk RSHIFT 1 -> ld 296 | hz RSHIFT 5 -> ic 297 | as RSHIFT 2 -> at 298 | NOT jy -> jz 299 | 1 AND am -> an 300 | ci OR ct -> cu 301 | hg AND hh -> hj 302 | jq OR jw -> jx 303 | v OR w -> x 304 | la LSHIFT 15 -> le 305 | dh AND dj -> dk 306 | dp AND dr -> ds 307 | jq AND jw -> jy 308 | au OR av -> aw 309 | NOT bf -> bg 310 | z OR aa -> ab 311 | ga AND gc -> gd 312 | hz AND ik -> im 313 | jt AND jv -> jw 314 | z AND aa -> ac 315 | jr OR js -> jt 316 | hb LSHIFT 1 -> hv 317 | hf OR hl -> hm 318 | ib OR ic -> id 319 | fq OR fr -> fs 320 | cq AND cs -> ct 321 | ia OR ig -> ih 322 | dd OR do -> dp 323 | d AND j -> l 324 | ib AND ic -> ie 325 | as RSHIFT 3 -> au 326 | be AND bg -> bh 327 | dd AND do -> dq 328 | NOT l -> m 329 | 1 AND gd -> ge 330 | y AND ae -> ag 331 | fo AND fz -> gb 332 | NOT ie -> if 333 | e AND f -> h 334 | x RSHIFT 3 -> z 335 | y OR ae -> af 336 | hf AND hl -> hn 337 | NOT h -> i 338 | NOT hn -> ho 339 | he RSHIFT 5 -> hh 340 | -------------------------------------------------------------------------------- /input8.txt: -------------------------------------------------------------------------------- 1 | "qxfcsmh" 2 | "ffsfyxbyuhqkpwatkjgudo" 3 | "byc\x9dyxuafof\\\xa6uf\\axfozomj\\olh\x6a" 4 | "jtqvz" 5 | "uzezxa\"jgbmojtwyfbfguz" 6 | "vqsremfk\x8fxiknektafj" 7 | "wzntebpxnnt\"vqndz\"i\x47vvjqo\"" 8 | "higvez\"k\"riewqk" 9 | "dlkrbhbrlfrp\\damiauyucwhty" 10 | "d\"" 11 | "qlz" 12 | "ku" 13 | "yy\"\"uoao\"uripabop" 14 | "saduyrntuswlnlkuppdro\\sicxosted" 15 | "tj" 16 | "zzphopswlwdhebwkxeurvizdv" 17 | "xfoheirjoakrpofles\"nfu" 18 | "q\xb7oh\"p\xce\"n" 19 | "qeendp\"ercwgywdjeylxcv" 20 | "dcmem" 21 | "\"i\x13r\"l" 22 | "ikso\xdcbvqnbrjduh\"uqudzki\xderwk" 23 | "wfdsn" 24 | "pwynglklryhtsqbno" 25 | "hcoj\x63iccz\"v\"ttr" 26 | "zf\x23\\hlj\\kkce\\d\\asy\"yyfestwcdxyfj" 27 | "xs" 28 | "m\"tvltapxdvtrxiy" 29 | "bmud" 30 | "k\"a" 31 | "b\"oas" 32 | "\"yexnjjupoqsxyqnquy\"uzfdvetqrc" 33 | "vdw\xe3olxfgujaj" 34 | "qomcxdnd\"\\cfoe\"" 35 | "fpul" 36 | "m\"avamefphkpv" 37 | "vvdnb\\x\\uhnxfw\"dpubfkxfmeuhnxisd" 38 | "hey\\" 39 | "ldaeigghlfey" 40 | "eure\"hoy\xa5iezjp\\tm" 41 | "yygb\"twbj\\r\"\x10gmxuhmp\"" 42 | "weirebp\x39mqonbtmfmd" 43 | "ltuz\\hs\"e" 44 | "ysvmpc" 45 | "g\x8amjtt\"megl\"omsaihifwa" 46 | "yimmm" 47 | "iiyqfalh" 48 | "cwknlaaf" 49 | "q\x37feg\xc6s\"xx" 50 | "uayrgeurgyp\\oi" 51 | "xhug\"pt\"axugllbdiggzhvy" 52 | "kdaarqmsjfx\xc3d" 53 | "\"vkwla" 54 | "d\"" 55 | "tmroz\"bvfinxoe\\mum\"wmm" 56 | "\"n\"bbswxne\\p\\yr\"qhwpdd" 57 | "skzlkietklkqovjhvj\xfe" 58 | "pbg\\pab\"bubqaf\"obzcwxwywbs\\dhtq" 59 | "xxjidvqh\"lx\\wu\"ij" 60 | "daef\x5fe\x5b\\kbeeb\x13qnydtboof" 61 | "ogvazaqy\"j\x73" 62 | "y" 63 | "n\"tibetedldy\\gsamm\"nwu" 64 | "wldkvgdtqulwkad" 65 | "dpmxnj" 66 | "twybw\"cdvf\"mjdajurokbce" 67 | "ru\"\\lasij\"i" 68 | "roc\\vra\\lhrm" 69 | "pbkt\x60booz\"fjlkc" 70 | "j\x4dytvjwrzt" 71 | "\\uiwjkniumxcs" 72 | "cbhm\"nexccior\"v\"j\"nazxilmfp\x47" 73 | "qdxngevzrlgoq" 74 | "\"lrzxftytpobsdfyrtdqpjbpuwmm\x9e" 75 | "mdag\x0asnck\xc2ggj\"slb\"fjy" 76 | "wyqkhjuazdtcgkcxvjkpnjdae" 77 | "aixfk\xc0iom\x21vueob" 78 | "dkiiakyjpkffqlluhaetires" 79 | "ysspv\"lysgkvnmwbbsy" 80 | "gy\"ryexcjjxdm\"xswssgtr" 81 | "s" 82 | "ddxv" 83 | "qwt\"\x27puilb\"pslmbrsxhrz" 84 | "qdg\xc9e\\qwtknlvkol\x54oqvmchn\\" 85 | "lvo" 86 | "b" 87 | "fk\"aa\"\"yenwch\\\\on" 88 | "srig\x63hpwaavs\\\x80qzk\"xa\"\xe6u\\wr" 89 | "yxjxuj\"ghyhhxfj\"\xa6qvatre" 90 | "yoktqxjxkzrklkoeroil" 91 | "\"jfmik\"" 92 | "smgseztzdwldikbqrh\"" 93 | "jftahgctf\"hoqy" 94 | "tcnhicr\"znpgckt\"ble" 95 | "vqktnkodh\"lo\"a\\bkmdjqqnsqr" 96 | "ztnirfzqq" 97 | "s" 98 | "xx" 99 | "iqj\"y\\hqgzflwrdsusasekyrxbp\\ad" 100 | "\\xzjhlaiynkioz\"\"bxepzimvgwt" 101 | "s\x36rbw" 102 | "mniieztwrisvdx" 103 | "atyfxioy\x2b\\" 104 | "irde\x85\x5cvbah\\jekw\"ia" 105 | "bdmftlhkwrprmpat\"prfaocvp" 106 | "w\\k" 107 | "umbpausy" 108 | "zfauhpsangy" 109 | "p\"zqyw" 110 | "wtztypyqvnnxzvlvipnq\"zu" 111 | "deicgwq\\oqvajpbov\\or\"kgplwu" 112 | "mbzlfgpi\\\\zqcidjpzqdzxityxa" 113 | "lfkxvhma" 114 | "\xf2yduqzqr\"\\fak\"p\"n" 115 | "mpajacfuxotonpadvng" 116 | "anb\\telzvcdu\\a\xf2flfq" 117 | "lrs\"ebethwpmuuc\"\x86ygr" 118 | "qmvdbhtumzc\"ci" 119 | "meet" 120 | "yopg\x0fdxdq\"h\\ugsu\xffmolxjv" 121 | "uhy" 122 | "fzgidrtzycsireghazscvmwcfmw\\t" 123 | "cqohkhpgvpru" 124 | "bihyigtnvmevx\"xx" 125 | "xz" 126 | "zofomwotzuxsjk\"q\"mc\"js\"dnmalhxd" 127 | "\\ktnddux\\fqvt\"ibnjntjcbn" 128 | "ia" 129 | "htjadnefwetyp\xd5kbrwfycbyy" 130 | "\"\\hkuxqddnao" 131 | "meqqsz\x83luecpgaem" 132 | "cvks\x87frvxo\"svqivqsdpgwhukmju" 133 | "sgmxiai\\o\"riufxwjfigr\xdf" 134 | "fgywdfecqufccpcdn" 135 | "faghjoq\x28abxnpxj" 136 | "zuppgzcfb\"dctvp\"elup\"zxkopx" 137 | "xqs\x45xxdqcihbwghmzoa" 138 | "anbnlp\\cgcvm\"hc" 139 | "xf\"fgrngwzys" 140 | "nrxsjduedcy\x24" 141 | "\x71sxl\"gj\"sds\"ulcruguz\\t\\ssvjcwhi" 142 | "jhj\"msch" 143 | "qpovolktfwyiuyicbfeeju\x01" 144 | "nkyxmb\"qyqultgt\"nmvzvvnxnb" 145 | "ycsrkbstgzqb\"uv\\cisn" 146 | "s" 147 | "ueptjnn\"\"sh" 148 | "lp\"z\"d\"mxtxiy" 149 | "yzjtvockdnvbubqabjourf\"k\"uoxwle" 150 | "\x82\"wqm\"" 151 | "\xb5cwtuks\x5fpgh" 152 | "wd" 153 | "tbvf" 154 | "ttbmzdgn" 155 | "vfpiyfdejyrlbgcdtwzbnm" 156 | "uc" 157 | "otdcmhpjagqix" 158 | "\\\xb1qso\"s" 159 | "scowax" 160 | "behpstjdh\xccqlgnqjyz\"eesn" 161 | "r\xe1cbnjwzveoomkzlo\\kxlfouhm" 162 | "jgrl" 163 | "kzqs\\r" 164 | "ctscb\x7fthwkdyko\"\x62pkf\"d\xe6knmhurg" 165 | "tc\"kw\x3ftt" 166 | "bxb\x5ccl" 167 | "jyrmfbphsldwpq" 168 | "jylpvysl\"\"juducjg" 169 | "en\\m\"kxpq\"wpb\\\"" 170 | "madouht\"bmdwvnyqvpnawiphgac\"" 171 | "vuxpk\"ltucrw" 172 | "aae\x60arr" 173 | "ttitnne\"kilkrgssnr\xfdurzh" 174 | "oalw" 175 | "pc\"\"gktkdykzbdpkwigucqni\"nxiqx" 176 | "dbrsaj" 177 | "bgzsowyxcbrvhtvekhsh\"qgd" 178 | "kudfemvk\"\"\"hkbrbil\"chkqoa" 179 | "zjzgj\\ekbhyfzufy" 180 | "\\acos\"fqekuxqzxbmkbnn\x1ejzwrm" 181 | "elxahvudn\"txtmomotgw" 182 | "\x2eoxmwdhelpr\"cgi\xf7pzvb" 183 | "eapheklx" 184 | "hfvma\"mietvc\"tszbbm\"czex" 185 | "h\"iiockj\\\xc1et" 186 | "d\"rmjjftm" 187 | "qlvhdcbqtyrhlc\\" 188 | "yy\"rsucjtulm\"coryri\"eqjlbmk" 189 | "tv" 190 | "r\"bfuht\\jjgujp\"" 191 | "kukxvuauamtdosngdjlkauylttaokaj" 192 | "srgost\"\"rbkcqtlccu\x65ohjptstrjkzy" 193 | "yxwxl\\yjilwwxffrjjuazmzjs" 194 | "dxlw\\fkstu\"hjrtiafhyuoh\"sewabne" 195 | "\x88sj\"v" 196 | "rfzprz\xec\"oxqclu\"krzefp\\q" 197 | "cfmhdbjuhrcymgxpylllyvpni" 198 | "ucrmjvmimmcq\x88\xd9\"lz" 199 | "lujtt\"" 200 | "gvbqoixn\"pmledpjmo\"flydnwkfxllf" 201 | "dvxqlbshhmelsk\x8big\"l" 202 | "mx\x54lma\x8bbguxejg" 203 | "\x66jdati\xeceieo" 204 | "\"iyyupixei\x54ff" 205 | "xohzf\"rbxsoksxamiu" 206 | "vlhthspeshzbppa\x4drhqnohjop\"\"mfjd" 207 | "f\"tvxxla\"vurian\"\"idjq\x3aptm\xc3olep" 208 | "gzqz" 209 | "kbq\\wogye\\altvi\\hbvmodny" 210 | "j\xd8" 211 | "ofjozdhkblvndl" 212 | "hbitoupimbawimxlxqze" 213 | "ypeleimnme" 214 | "xfwdrzsc\\oxqamawyizvi\\y" 215 | "enoikppx\xa1ixe\"yo\"gumye" 216 | "fb" 217 | "vzf" 218 | "zxidr" 219 | "cu\x31beirsywtskq" 220 | "lxpjbvqzztafwezd" 221 | "\\jyxeuo\x18bv" 222 | "b\"vawc\"p\\\\giern\"b" 223 | "odizunx\"\"t\\yicdn\"x\"sdiz" 224 | "\"\"tebrtsi" 225 | "ctyzsxv\xa6pegfkwsi\"tgyltaakytccb" 226 | "htxwbofchvmzbppycccliyik\xe5a" 227 | "ggsslefamsklezqkrd" 228 | "rcep\"fnimwvvdx\"l" 229 | "zyrzlqmd\x12egvqs\\llqyie" 230 | "\x07gsqyrr\\rcyhyspsvn" 231 | "butg\"" 232 | "gb" 233 | "gywkoxf\"jsg\\wtopxvumirqxlwz" 234 | "rj\"ir\"wldwveair\x2es\"dhjrdehbqnzl" 235 | "ru\"elktnsbxufk\\ejufjfjlevt\\lrzd" 236 | "\"widsvok" 237 | "oy\"\x81nuesvw" 238 | "ay" 239 | "syticfac\x1cfjsivwlmy\"pumsqlqqzx" 240 | "m" 241 | "rjjkfh\x78cf\x2brgceg\"jmdyas\"\\xlv\xb6p" 242 | "tmuvo\"\x3ffdqdovjmdmkgpstotojkv\"as" 243 | "jd\\ojvynhxllfzzxvbn\"wrpphcvx" 244 | "pz" 245 | "\"twr" 246 | "n\\hdzmxe\"mzjjeadlz" 247 | "fb\"rprxuagvahjnri" 248 | "rfmexmjjgh\\xrnmyvnatrvfruflaqjnd" 249 | "obbbde\"co\"qr\"qpiwjgqahqm\\jjp\"" 250 | "vpbq\"\"y\"czk\\b\x52ed\"lnzepobp" 251 | "syzeajzfarplydipny\"y\"\xe8ad" 252 | "mpyodwb" 253 | "\x47rakphlqqptd" 254 | "wa\"oj\"aiy" 255 | "a" 256 | "ropozx" 257 | "q\x51nbtlwa" 258 | "etukvgx\\jqxlkq" 259 | "\"tp\"rah\"pg\"s\"bpdtes\\tkasdhqd" 260 | "dn\"qqpkikadowssb\xcah\"dzpsf\\ect\"jdh" 261 | "pxunovbbrrn\\vullyn\"bno\"\"\"myfxlp\"" 262 | "qaixyazuryvkmoulhcqaotegfj\\mpzm" 263 | "bvfrbicutzbjwn\\oml\"cf\"d\"ezcpv\"j" 264 | "rmbrdtneudemigdhelmb" 265 | "aq\\aurmbhy" 266 | "wujqvzw" 267 | "gf\"tssmvm\"gm\"hu\x9a\xb7yjawsa" 268 | "hrhqqxow\xe2gsydtdspcfqy\"zw\\ou" 269 | "ianwwf\\yko\\tdujhhqdi" 270 | "xylz\"zpvpab" 271 | "lwuopbeeegp" 272 | "aoop\x49jhhcexdmdtun" 273 | "\\\\mouqqcsgmz" 274 | "tltuvwhveau\x43b\"ymxjlcgiymcynwt" 275 | "gsugerumpyuhtjljbhrdyoj" 276 | "lnjm\xb8wg\"ajh" 277 | "zmspue\"nfttdon\\b\"eww" 278 | "\"w\x67jwaq\x7ernmyvs\\rmdsuwydsd\"th" 279 | "ogtgvtlmcvgllyv" 280 | "z\"fqi\"rvddoehrciyl" 281 | "yustxxtot\"muec\"xvfdbzunzvveq" 282 | "mqslw" 283 | "txqnyvzmibqgjs\xb6xy\x86nfalfyx" 284 | "kzhehlmkholov" 285 | "plpmywcnirrjutjguosh\\" 286 | "pydbnqofv\"dn\\m" 287 | "aegqof" 288 | "eambmxt\\dxagoogl\\zapfwwlmk" 289 | "afbmqitxxqhddlozuxcpjxgh" 290 | "vgts" 291 | "bfdpqtoxzzhmzcilehnflna" 292 | "s\"idpz" 293 | "\xcfhgly\"nlmztwybx\"ecezmsxaqw" 294 | "aackfgndqcqiy" 295 | "\x22unqdlsrvgzfaohoffgxzfpir\"s" 296 | "abh\"ydv\"kbpdhrerl" 297 | "bdzpg" 298 | "ekwgkywtmzp" 299 | "wtoodejqmrrgslhvnk\"pi\"ldnogpth" 300 | "njro\x68qgbx\xe4af\"\\suan" 301 | -------------------------------------------------------------------------------- /input9.txt: -------------------------------------------------------------------------------- 1 | Tristram to AlphaCentauri = 34 2 | Tristram to Snowdin = 100 3 | Tristram to Tambi = 63 4 | Tristram to Faerun = 108 5 | Tristram to Norrath = 111 6 | Tristram to Straylight = 89 7 | Tristram to Arbre = 132 8 | AlphaCentauri to Snowdin = 4 9 | AlphaCentauri to Tambi = 79 10 | AlphaCentauri to Faerun = 44 11 | AlphaCentauri to Norrath = 147 12 | AlphaCentauri to Straylight = 133 13 | AlphaCentauri to Arbre = 74 14 | Snowdin to Tambi = 105 15 | Snowdin to Faerun = 95 16 | Snowdin to Norrath = 48 17 | Snowdin to Straylight = 88 18 | Snowdin to Arbre = 7 19 | Tambi to Faerun = 68 20 | Tambi to Norrath = 134 21 | Tambi to Straylight = 107 22 | Tambi to Arbre = 40 23 | Faerun to Norrath = 11 24 | Faerun to Straylight = 66 25 | Faerun to Arbre = 144 26 | Norrath to Straylight = 115 27 | Norrath to Arbre = 135 28 | Straylight to Arbre = 127 29 | --------------------------------------------------------------------------------