summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authortomsmeding <tom.smeding@gmail.com>2019-12-25 14:24:05 +0100
committertomsmeding <tom.smeding@gmail.com>2019-12-25 14:24:05 +0100
commit1fb24f91c66fb320721760a2f8fa92f1e873b4c4 (patch)
tree63233f34ee16ba55251a433ba5ac30ad94189062
parent83ed445f43e23f35b46d76ea53c4ab74e1115e9e (diff)
Day 25 🎄
-rw-r--r--2019/25.hs209
-rw-r--r--2019/25.in1
2 files changed, 210 insertions, 0 deletions
diff --git a/2019/25.hs b/2019/25.hs
new file mode 100644
index 0000000..3494fab
--- /dev/null
+++ b/2019/25.hs
@@ -0,0 +1,209 @@
+{-# LANGUAGE MultiWayIf #-}
+module Main where
+
+import Control.Monad
+import Data.Char
+import Data.List
+import Data.Ord
+import qualified Data.Set as Set
+import qualified Data.Map.Strict as Map
+import System.IO
+import Text.Parsec hiding (getInput)
+
+import Debug.Trace
+
+import Input
+import qualified IntCode as IC
+
+
+cyan, blue :: String -> String
+cyan s = "\x1B[36m" ++ s ++ "\x1B[0m"
+blue s = "\x1B[34m" ++ s ++ "\x1B[0m"
+
+
+type Name = String
+type Item = String
+
+data Meta = Killed | Taken Item | WTF String
+ deriving (Show)
+
+data Dir = North | East | West | South
+ deriving (Enum, Eq, Ord)
+
+instance Show Dir where
+ show North = "north"
+ show East = "east"
+ show West = "west"
+ show South = "south"
+
+instance Read Dir where
+ readsPrec _ ('n':'o':'r':'t':'h':s) = [(North, s)]
+ readsPrec _ ('e':'a':'s':'t':s) = [(East, s)]
+ readsPrec _ ('w':'e':'s':'t':s) = [(West, s)]
+ readsPrec _ ('s':'o':'u':'t':'h':s) = [(South, s)]
+ readsPrec _ _ = []
+
+data RoomDesc
+ = RoomDesc { rName :: Name
+ , rDesc :: String
+ , rDoors :: [Dir]
+ , rItems :: [Item] }
+ deriving (Show)
+
+parseOutput :: String -> Either Meta RoomDesc
+parseOutput = either (\e -> Left (WTF (show e))) id . parse pRoom ""
+ where
+ pRoom = do
+ spaces
+ choice [do
+ void $ string "You take the "
+ item <- many (satisfy (/= '.'))
+ void $ char '.'
+ void $ newline
+ return (Left (Taken item))
+ ,do
+ name <- pName
+ desc <- pDesc
+ spaces
+ void $ string "Doors here lead:\n"
+ dirStrs <- pList
+ spaces
+ items <- choice [string "Items here:\n" >> pList
+ ,return []]
+ spaces
+ void $ string "Command?\n"
+ return (Right (RoomDesc name desc (map read dirStrs) items))
+ ]
+ pName = do
+ void $ string "== "
+ name <- many (notFollowedBy (try (string " ==")) >> anyChar)
+ void $ string " =="
+ void $ newline
+ return name
+ pDesc = pRestOfLine
+ pList = many (string "- " >> pRestOfLine <* newline)
+ pRestOfLine = many (satisfy (/= '\n'))
+
+data Explorer = Explorer (Map.Map Name (RoomDesc, Map.Map Dir Name)) (Maybe Name) (Maybe (Name, Dir))
+ deriving (Show)
+
+observe :: Explorer -> RoomDesc -> Explorer
+observe (Explorer chart _ lastMove) rd =
+ let chart' = case Map.lookup (rName rd) chart of
+ Nothing -> Map.insert (rName rd) (rd, mempty) chart
+ Just _ -> chart
+ in case lastMove of
+ Nothing -> Explorer chart' (Just (rName rd)) lastMove
+ Just (from, dir) ->
+ let Just (fromRD, dirmap) = Map.lookup from chart
+ chart'' = Map.insert from (fromRD, Map.insert dir (rName rd) dirmap) chart'
+ in Explorer chart'' (Just (rName rd)) lastMove
+
+chooseMove :: Explorer -> Maybe (Dir, Explorer)
+chooseMove (Explorer _ Nothing _) = undefined
+chooseMove (Explorer chart (Just current@"Security Checkpoint") _) =
+ Just (South, Explorer chart (Just current) (Just (current, South)))
+chooseMove (Explorer chart (Just current) _) =
+ let Just (rd, dirmap) = Map.lookup current chart
+ opts = [case Map.lookup dir dirmap of
+ Just room' -> (dir, distToUnex room' 1 (Set.singleton current))
+ Nothing -> (dir, 1)
+ | dir <- rDoors rd]
+ in traceShow opts $
+ case minimumBy (comparing snd) ((undefined, maxBound) : opts) of
+ (_, n) | n == maxBound -> Nothing
+ (dir, _) -> Just (dir, Explorer chart (Just current) (Just (current, dir)))
+ where
+ distToUnex :: Name -> Int -> Set.Set Name -> Int
+ distToUnex "Security Checkpoint" _ _ = maxBound
+ distToUnex room dist visited =
+ let Just (rd, dirmap) = Map.lookup room chart
+ in if | room `Set.member` visited ->
+ maxBound
+ | not . null $ rDoors rd \\ Map.keys dirmap ->
+ dist + 1
+ | otherwise ->
+ minimum [distToUnex room' (dist + 1) (Set.insert room visited)
+ | room' <- Map.elems dirmap]
+
+printDOT :: Explorer -> String
+printDOT (Explorer chart _ _) = "digraph G {\n" ++ printRelations "Hull Breach" mempty ++ "}"
+ where
+ printRelations room seen
+ | room `Set.member` seen = ""
+ | otherwise =
+ let Just (rd, dirmap) = Map.lookup room chart
+ in concat ((show room ++ " [label=" ++ show (room ++ "\n" ++ show (rItems rd)) ++ "];\n")
+ : unlines [show room ++ " -> " ++ show to ++ " [label=" ++ show (show dir) ++ "];"
+ | (dir, to) <- Map.assocs dirmap]
+ : [printRelations to (Set.insert room seen) | to <- Map.elems dirmap])
+
+exploreAndPrintMap :: [Integer] -> IO ()
+exploreAndPrintMap program =
+ let loop cont inp expl =
+ case IC.runContinue cont inp of
+ Left (cont', out) -> do
+ let out' = map (chr . fromIntegral) out
+ putStr (cyan out') >> hFlush stdout
+ case parseOutput out' of
+ Right rd ->
+ case chooseMove (observe expl rd) of
+ Just (dir, expl') -> do
+ putStrLn (blue ("Entering '" ++ show dir ++ "'"))
+ loop cont' (map (fromIntegral . ord) (show dir ++ "\n")) expl'
+ Nothing -> do
+ putStrLn "Explorer gave up!"
+ putStrLn (printDOT expl)
+ Left err -> do
+ print err
+ putStrLn (printDOT expl)
+ Right (_, out) -> do
+ putStr (cyan (map (chr . fromIntegral) out))
+ in loop (IC.initialContinuation program) [] (Explorer mempty Nothing Nothing)
+
+interactive :: [Integer] -> IO ()
+interactive program =
+ let loop cont inp =
+ case IC.runContinue cont inp of
+ Left (cont', out) -> do
+ putStr (map (chr . fromIntegral) out)
+ line <- getLine
+ loop cont' (map (fromIntegral . ord) (line ++ "\n"))
+ Right (_, out) -> do
+ putStr (map (chr . fromIntegral) out)
+ in loop (IC.initialContinuation program) []
+
+tryCombinations :: [Integer] -> IO ()
+tryCombinations program =
+ let loop _ _ [] = putStrLn "Out of tries!"
+ loop cont inp (current:nexts) =
+ case IC.runContinue cont inp of
+ Left (cont', out) -> do
+ let out' = map (chr . fromIntegral) out
+ -- putStrLn out'
+ if | "lighter" `isInfixOf` out' -> putStrLn " -> heavy"
+ | "heavier" `isInfixOf` out' -> putStrLn " -> light"
+ | otherwise -> return ()
+ print current
+ let input = concat [concat ["take " ++ i ++ "\n" | i <- current]
+ ,"east\n"
+ ,concat ["drop " ++ i ++ "\n" | i <- current]]
+ loop cont' (map (fromIntegral . ord) input) nexts
+ Right (_, out) -> do
+ putStr (map (chr . fromIntegral) out)
+ setupString = "east\ntake antenna\nnorth\nnorth\ntake asterisk\nsouth\nwest\nwest\ntake astronaut ice cream\neast\nsouth\ntake hologram\nnorth\neast\nsouth\neast\ntake ornament\nnorth\nwest\ntake fixed point\neast\nsouth\nwest\nwest\nsouth\nsouth\nsouth\ntake dark matter\nnorth\nwest\nnorth\ntake monolith\nnorth\nnorth\ndrop astronaut ice cream\ndrop hologram\ndrop fixed point\ndrop asterisk\ndrop ornament\ndrop dark matter\ndrop monolith\ndrop antenna\n"
+ allItems = ["asterisk", "ornament", "dark matter", "monolith", "antenna", "astronaut ice cream", "hologram", "fixed point"]
+ combinations [] = [[]]
+ combinations (x:xs) = let l = combinations xs in map (x:) l ++ l
+ in loop (IC.initialContinuation program) (map (fromIntegral . ord) setupString) (combinations allItems)
+
+main :: IO ()
+main = do
+ program <- IC.parse . head <$> getInput 25
+
+ -- exploreAndPrintMap program
+ -- interactive program
+ tryCombinations program
+
+ -- Collection of items: ["asterisk","ornament","astronaut ice cream","fixed point"]
+ -- Password: 134227456
diff --git a/2019/25.in b/2019/25.in
new file mode 100644
index 0000000..c36b9c5
--- /dev/null
+++ b/2019/25.in
@@ -0,0 +1 @@
+109,4806,21101,0,3124,1,21102,13,1,0,1105,1,1424,21102,166,1,1,21102,24,1,0,1105,1,1234,21101,31,0,0,1106,0,1984,1106,0,13,6,4,3,2,52,51,21,4,28,56,55,3,19,-9,-10,47,89,88,90,90,6,77,73,85,71,1,76,68,63,65,22,-27,70,76,81,87,5,105,105,107,108,95,4,97,92,109,109,5,110,105,110,108,95,4,115,96,109,109,13,-3,59,101,85,92,97,13,84,80,92,78,34,-15,26,-16,46,88,72,79,84,0,72,76,-3,85,74,79,75,-8,64,68,75,57,65,70,64,66,72,8,-41,32,-22,56,77,82,-4,60,76,62,70,-2,74,-11,55,52,68,67,73,56,60,52,-20,44,56,66,-24,48,58,42,49,54,-16,-53,10,0,56,99,96,95,82,94,83,45,-9,23,-13,61,85,88,74,71,82,73,79,73,89,67,65,-4,62,73,70,69,56,68,57,2,-35,24,-14,64,85,90,4,70,67,79,7,83,-2,68,75,-5,78,65,57,75,-10,76,53,76,0,-37,31,-21,57,78,83,-3,64,74,72,0,76,-9,73,58,57,-13,70,57,49,67,-18,54,64,48,55,-23,48,44,56,42,-14,-51,14,-4,74,95,100,14,97,77,86,79,9,92,79,75,5,27,-17,61,82,87,1,68,78,76,4,80,-5,66,58,78,60,-10,73,60,52,70,-15,57,67,51,58,-6,-43,14,-4,74,95,100,14,81,94,90,90,9,92,79,75,5,60,-50,23,42,38,-32,38,39,30,42,47,-38,30,36,28,25,41,38,34,31,18,23,29,19,33,-52,20,29,-55,27,27,27,8,15,-61,22,16,-64,24,13,18,-54,-69,-70,-14,7,12,-74,-8,-11,1,-71,5,-80,-4,-3,3,-15,-84,-85,-109,29,-19,59,80,85,-1,82,62,71,64,-6,77,64,60,-10,62,66,57,59,63,57,67,51,-19,56,58,57,57,-10,-47,44,-34,39,58,54,-16,60,61,57,64,48,56,-23,52,40,60,38,-28,44,53,-31,55,32,55,-35,48,42,41,-39,32,38,42,-42,-44,12,33,38,-48,28,19,25,32,-52,-76,-77,59,-49,13,55,-30,42,51,-33,49,50,32,31,31,39,36,48,-42,24,35,32,34,29,21,35,19,25,37,-53,14,10,26,18,-57,-59,-3,18,23,-63,1,17,3,-67,1,-4,14,-2,6,-73,-8,14,-76,-12,-78,-40,2,4,-13,-82,-106,-107,35,-25,53,74,79,0,74,60,-10,65,53,72,64,52,56,52,50,-19,53,57,62,56,-24,58,54,38,39,40,-29,-31,2,56,35,-34,-58,-59,138,-128,-74,-108,-33,-31,-26,-44,-101,-114,-33,-37,-51,-39,-35,-47,-54,-122,-37,-45,-52,-59,-58,-128,-46,-65,-42,-49,-133,-132,-102,-60,-68,-56,-55,-139,-141,-106,-61,-65,-72,-78,-64,-148,-70,-72,-151,-68,-81,-81,-72,-156,-74,-86,-86,-80,-161,-97,-81,-95,-165,-94,-98,-103,-83,-97,-102,-90,-173,-90,-103,-111,-99,-178,-95,-108,-112,-182,-115,-115,-101,-117,-120,-104,-120,-122,-191,-106,-128,-118,-110,-127,-196,-196,-199,-135,-123,-134,-203,-115,-126,-121,-207,-143,-127,-141,-211,-143,-139,-145,-148,-132,-148,-150,-219,-154,-156,-155,-148,-224,-141,-147,-227,-144,-157,-161,-231,-165,-161,-165,-168,-161,-157,-159,-166,-162,-157,-228,-265,138,-128,-74,-108,-33,-31,-26,-44,-101,-114,-33,-37,-51,-39,-35,-47,-54,-122,-37,-45,-52,-59,-58,-128,-46,-65,-42,-49,-133,-132,-102,-60,-68,-56,-55,-139,-141,-106,-61,-65,-72,-78,-64,-148,-70,-72,-151,-68,-81,-81,-72,-156,-74,-86,-86,-80,-161,-97,-81,-95,-165,-90,-94,-97,-97,-86,-102,-90,-173,-90,-103,-111,-99,-178,-95,-108,-112,-182,-115,-115,-101,-117,-120,-104,-120,-122,-191,-106,-128,-118,-110,-127,-196,-196,-199,-135,-123,-134,-203,-115,-126,-121,-207,-143,-127,-141,-211,-143,-139,-145,-148,-132,-148,-150,-219,-154,-156,-155,-148,-224,-141,-147,-227,-144,-157,-161,-231,-165,-161,-165,-168,-161,-157,-159,-166,-162,-157,-228,-265,263,-253,-199,-233,-158,-156,-151,-169,-226,-239,-158,-162,-176,-164,-160,-172,-179,-247,-162,-170,-177,-184,-183,-253,-171,-190,-167,-174,-258,-257,-227,-183,-197,-187,-175,-182,-193,-184,-268,-202,-191,-194,-192,-197,-205,-191,-207,-276,-278,-222,-201,-196,-282,-206,-219,-196,-286,-207,-206,-210,-223,-222,-223,-225,-280,-293,-296,-232,-220,-231,-300,-212,-223,-218,-304,-236,-228,-223,-239,-227,-310,-227,-240,-244,-314,-248,-237,-250,-243,-239,-247,-237,-308,-345,-273,-260,-248,-243,-263,-329,-252,-252,-248,-260,-267,-266,-253,-337,-249,-260,-255,-259,-342,-260,-267,-280,-270,-271,-348,-281,-268,-272,-279,-285,-342,-355,-280,-278,-279,-284,-277,-361,-282,-278,-274,-275,-290,-298,-300,-369,-300,-292,-290,-373,-309,-375,-299,-298,-301,-310,-302,-297,-370,-383,-302,-316,-321,-311,-315,-299,-321,-308,-392,-306,-322,-330,-312,-397,-326,-334,-317,-401,-330,-338,-324,-325,-337,-329,-339,-341,-398,-411,-347,-335,-346,-415,-334,-352,-350,-346,-341,-338,-422,-334,-345,-340,-344,-427,-345,-357,-357,-351,-432,-365,-361,-353,-367,-370,-354,-363,-351,-427,-464,-441,-397,-373,-434,-447,-376,-380,-374,-375,-373,-452,-454,-398,-377,-372,-458,-376,-388,-382,-377,-387,-396,-465,-400,-398,-468,-404,-404,-395,-403,-473,-390,-396,-476,-406,-409,-395,-480,-408,-404,-483,-418,-396,-486,-403,-399,-409,-417,-413,-421,-493,37,-5,73,71,-8,75,62,58,-12,62,55,74,64,48,50,-19,45,63,-22,61,48,44,-26,50,37,44,48,-31,33,40,48,41,43,30,37,-25,-38,-63,0,0,109,7,21101,0,0,-2,22208,-2,-5,-1,1205,-1,1169,22202,-2,-4,1,22201,1,-6,1,22102,1,-2,2,21101,0,1162,0,2106,0,-3,21201,-2,1,-2,1106,0,1136,109,-7,2105,1,0,109,6,2102,1,-5,1181,21002,0,1,-2,21101,0,0,-3,21201,-5,1,-5,22208,-3,-2,-1,1205,-1,1229,2201,-5,-3,1204,21001,0,0,1,22102,1,-3,2,22101,0,-2,3,21101,0,1222,0,2105,1,-4,21201,-3,1,-3,1106,0,1192,109,-6,2106,0,0,109,2,21201,-1,0,1,21102,1256,1,2,21102,1,1251,0,1105,1,1174,109,-2,2106,0,0,109,5,22201,-4,-3,-1,22201,-2,-1,-1,204,-1,109,-5,2106,0,0,109,3,2101,0,-2,1280,1006,0,1303,104,45,104,32,1201,-1,66,1292,20101,0,0,1,21102,1,1301,0,1106,0,1234,104,10,109,-3,2105,1,0,0,0,109,2,1202,-1,1,1309,1101,0,0,1308,21101,4601,0,1,21102,13,1,2,21101,0,4,3,21101,0,1353,4,21102,1343,1,0,1106,0,1130,20102,1,1308,-1,109,-2,2106,0,0,74,109,3,1202,-2,1,1360,20008,0,1309,-1,1206,-1,1419,1005,1308,1398,1101,0,1,1308,21008,1309,-1,-1,1206,-1,1387,21102,1,106,1,1105,1,1391,21101,0,92,1,21102,1,1398,0,1105,1,1234,104,45,104,32,1201,-2,1,1408,20102,1,0,1,21101,1417,0,0,1105,1,1234,104,10,109,-3,2105,1,0,109,3,1201,-2,0,1128,21101,0,34,1,21101,0,1441,0,1106,0,1234,1001,1128,0,1446,21002,0,1,1,21101,1456,0,0,1106,0,1234,21102,1,41,1,21102,1467,1,0,1105,1,1234,1001,1128,1,1473,20102,1,0,1,21102,1,1482,0,1105,1,1234,21102,46,1,1,21102,1,1493,0,1105,1,1234,21001,1128,3,1,21102,4,1,2,21102,1,1,3,21101,1273,0,4,21102,1,1516,0,1106,0,1130,21001,1128,0,1,21101,0,1527,0,1106,0,1310,1001,1128,2,1533,20101,0,0,-1,1206,-1,1545,21101,0,1545,0,2105,1,-1,109,-3,2106,0,0,109,0,99,109,2,1102,0,1,1550,21101,0,4601,1,21102,1,13,2,21102,4,1,3,21102,1,1664,4,21101,0,1582,0,1106,0,1130,2,2486,1352,1551,1102,0,1,1552,20102,1,1550,1,21102,1,33,2,21102,1,1702,3,21101,1609,0,0,1105,1,2722,21007,1552,0,-1,1205,-1,1630,20107,0,1552,-1,1205,-1,1637,21102,1630,1,0,1105,1,1752,21102,548,1,1,1105,1,1641,21101,0,687,1,21102,1,1648,0,1105,1,1234,21101,4457,0,1,21102,1,1659,0,1106,0,1424,109,-2,2106,0,0,109,4,21202,-2,-1,-2,2101,0,-3,1675,21008,0,-1,-1,1206,-1,1697,1201,-3,2,1687,20101,-27,0,-3,22201,-3,-2,-3,2001,1550,-3,1550,109,-4,2105,1,0,109,5,21008,1552,0,-1,1206,-1,1747,1201,-3,1901,1717,20102,1,0,-2,1205,-4,1736,20207,-2,1551,-1,1205,-1,1747,1102,1,-1,1552,1106,0,1747,22007,1551,-2,-1,1205,-1,1747,1101,0,1,1552,109,-5,2105,1,0,109,1,21102,1,826,1,21102,1,1765,0,1106,0,1234,21001,1550,0,1,21102,1,1776,0,1105,1,2863,21102,1090,1,1,21101,0,1787,0,1106,0,1234,99,1105,1,1787,109,-1,2106,0,0,109,1,21102,512,1,1,21102,1,1809,0,1105,1,1234,99,1105,1,1809,109,-1,2106,0,0,109,1,1102,1,1,1129,109,-1,2106,0,0,109,1,21101,377,0,1,21101,0,1842,0,1105,1,1234,1105,1,1831,109,-1,2105,1,0,109,1,21102,1,407,1,21102,1863,1,0,1106,0,1234,99,1105,1,1863,109,-1,2105,1,0,109,1,21101,452,0,1,21101,1885,0,0,1106,0,1234,99,1106,0,1885,109,-1,2105,1,0,1941,1947,1953,1958,1965,1972,1978,4575,4923,4527,4604,5024,5218,4671,4646,5043,4683,5005,4580,4541,5168,4938,4981,4562,4602,4852,5202,4609,4790,5221,5228,5072,4959,5090,4803,4541,5076,4608,5006,4867,2281,2468,2418,2450,2487,2125,2505,5,95,108,104,104,23,5,96,91,108,108,1,4,101,105,112,3,6,104,104,106,107,94,-1,6,109,104,109,107,94,-1,5,111,91,100,93,23,5,114,95,108,108,1,109,3,21101,0,1993,0,1106,0,2634,1006,1129,2010,21102,1,316,1,21102,2007,1,0,1105,1,1234,1105,1,2076,21101,0,0,-1,1201,-1,1894,2019,21002,0,1,1,21101,0,0,2,21101,0,0,3,21101,0,2037,0,1106,0,2525,1206,1,2054,1201,-1,1934,2050,21101,2051,0,0,106,0,0,1105,1,2076,21201,-1,1,-1,21207,-1,7,-2,1205,-2,2014,21101,0,177,1,21101,2076,0,0,1105,1,1234,109,-3,2106,0,0,109,3,2001,1128,-2,2088,21002,0,1,-1,1205,-1,2108,21101,0,201,1,21101,0,2105,0,1105,1,1234,1105,1,2119,21201,-1,0,1,21101,2119,0,0,1105,1,1424,109,-3,2105,1,0,0,109,1,1101,0,0,2124,21101,4601,0,1,21102,1,13,2,21102,4,1,3,21102,2173,1,4,21101,0,2154,0,1105,1,1130,1005,2124,2168,21102,226,1,1,21102,1,2168,0,1106,0,1234,109,-1,2105,1,0,109,3,1005,2124,2275,1201,-2,0,2183,20008,0,1128,-1,1206,-1,2275,1201,-2,1,2195,20102,1,0,-1,21201,-1,0,1,21102,1,5,2,21101,1,0,3,21101,0,2216,0,1106,0,2525,1206,1,2275,21101,0,258,1,21101,2230,0,0,1105,1,1234,22102,1,-1,1,21101,0,2241,0,1106,0,1234,104,46,104,10,1102,1,1,2124,1201,-2,0,2256,1101,-1,0,0,1201,-2,3,2263,20102,1,0,-1,1206,-1,2275,21102,2275,1,0,2106,0,-1,109,-3,2105,1,0,0,109,1,1102,1,0,2280,21102,1,4601,1,21101,13,0,2,21101,0,4,3,21101,0,2329,4,21101,2310,0,0,1105,1,1130,1005,2280,2324,21102,1,273,1,21102,1,2324,0,1106,0,1234,109,-1,2105,1,0,109,3,1005,2280,2413,1201,-2,0,2339,21008,0,-1,-1,1206,-1,2413,1201,-2,1,2350,21001,0,0,-1,21201,-1,0,1,21102,5,1,2,21101,0,1,3,21102,1,2372,0,1106,0,2525,1206,1,2413,21101,301,0,1,21102,2386,1,0,1105,1,1234,22101,0,-1,1,21102,2397,1,0,1106,0,1234,104,46,104,10,1101,0,1,2280,1201,-2,0,2412,102,1,1128,0,109,-3,2106,0,0,109,1,21102,-1,1,1,21102,2431,1,0,1105,1,1310,1205,1,2445,21101,133,0,1,21102,2445,1,0,1106,0,1234,109,-1,2106,0,0,109,1,21101,3,0,1,21101,2463,0,0,1105,1,2081,109,-1,2106,0,0,109,1,21102,1,4,1,21101,0,2481,0,1105,1,2081,109,-1,2105,1,0,70,109,1,21102,5,1,1,21102,2500,1,0,1106,0,2081,109,-1,2105,1,0,109,1,21102,1,6,1,21101,0,2518,0,1106,0,2081,109,-1,2106,0,0,0,0,109,5,1201,-3,0,2523,1101,0,1,2524,21201,-4,0,1,21102,1,2585,2,21101,2550,0,0,1106,0,1174,1206,-2,2576,1202,-4,1,2558,2001,0,-3,2566,101,3094,2566,2566,21008,0,-1,-1,1205,-1,2576,1102,1,0,2524,21001,2524,0,-4,109,-5,2106,0,0,109,5,22201,-4,-3,-4,22201,-4,-2,-4,21208,-4,10,-1,1206,-1,2606,21101,0,-1,-4,201,-3,2523,2615,1001,2615,3094,2615,21002,0,1,-1,22208,-4,-1,-1,1205,-1,2629,1101,0,0,2524,109,-5,2105,1,0,109,4,21102,3094,1,1,21102,1,30,2,21102,1,1,3,21102,2706,1,4,21101,2659,0,0,1105,1,1130,21101,0,0,-3,203,-2,21208,-2,10,-1,1205,-1,2701,21207,-2,0,-1,1205,-1,2663,21207,-3,29,-1,1206,-1,2663,2101,3094,-3,2693,2101,0,-2,0,21201,-3,1,-3,1106,0,2663,109,-4,2105,1,0,109,2,2101,0,-1,2715,1101,-1,0,0,109,-2,2106,0,0,0,109,5,2102,1,-2,2721,21207,-4,0,-1,1206,-1,2739,21102,0,1,-4,22101,0,-4,1,22101,0,-3,2,21101,1,0,3,21101,2758,0,0,1106,0,2763,109,-5,2106,0,0,109,6,21207,-4,1,-1,1206,-1,2786,22207,-5,-3,-1,1206,-1,2786,22101,0,-5,-5,1105,1,2858,22102,1,-5,1,21201,-4,-1,2,21202,-3,2,3,21101,0,2805,0,1105,1,2763,21202,1,1,-5,21101,0,1,-2,22207,-5,-3,-1,1206,-1,2824,21102,0,1,-2,22202,-3,-2,-3,22107,0,-4,-1,1206,-1,2850,21202,-2,1,1,21201,-4,-1,2,21101,0,2850,0,106,0,2721,21202,-3,-1,-3,22201,-5,-3,-5,109,-6,2106,0,0,109,3,21208,-2,0,-1,1205,-1,2902,21207,-2,0,-1,1205,-1,2882,1106,0,2888,104,45,21202,-2,-1,-2,22101,0,-2,1,21102,1,2899,0,1105,1,2909,1106,0,2904,104,48,109,-3,2105,1,0,109,4,22101,0,-3,1,21101,10,0,2,21101,0,2926,0,1106,0,3010,22101,0,1,-2,22101,0,2,-1,1206,-2,2948,22102,1,-2,1,21101,2948,0,0,1106,0,2909,22101,48,-1,-1,204,-1,109,-4,2106,0,0,1,2,4,8,16,32,64,128,256,512,1024,2048,4096,8192,16384,32768,65536,131072,262144,524288,1048576,2097152,4194304,8388608,16777216,33554432,67108864,134217728,268435456,536870912,1073741824,2147483648,4294967296,8589934592,17179869184,34359738368,68719476736,137438953472,274877906944,549755813888,1099511627776,2199023255552,4398046511104,8796093022208,17592186044416,35184372088832,70368744177664,140737488355328,281474976710656,562949953421312,1125899906842624,109,8,21102,1,0,-4,21101,0,0,-3,21102,1,51,-2,21201,-2,-1,-2,1201,-2,2959,3033,21002,0,1,-1,21202,-3,2,-3,22207,-7,-1,-5,1205,-5,3059,21201,-3,1,-3,22102,-1,-1,-5,22201,-7,-5,-7,22207,-3,-6,-5,1205,-5,3078,22102,-1,-6,-5,22201,-3,-5,-3,22201,-1,-4,-4,1205,-2,3024,21202,-4,1,-7,22102,1,-3,-6,109,-8,2106,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,3131,3143,0,3821,3405,3252,0,11,61,105,95,94,17,50,97,83,78,79,83,108,-19,2,7,-79,-9,-2,2,-83,-11,-7,-86,-3,-16,-7,-11,-6,-21,-21,-94,-30,-96,-25,-19,-23,-31,-101,-29,-25,-104,-21,-34,-38,-108,-39,-34,-32,-33,-31,-114,-43,-47,-35,-49,-105,-120,-69,-43,-123,-49,-56,-57,-47,-128,-40,-51,-46,-50,-133,-51,-63,-63,-57,-138,-69,-58,-62,-65,-143,-79,-69,-63,-68,-148,-79,-68,-82,-83,-63,-81,-77,-85,-145,-158,-75,-88,-92,-162,-91,-85,-89,-97,-167,-96,-104,-87,-171,-106,-104,-105,-97,-176,-94,-109,-114,-104,-112,-114,-169,3259,3268,0,3124,0,3341,0,8,75,96,89,96,20,53,83,106,72,11,44,38,37,35,37,38,36,-48,17,29,33,20,-53,-4,14,12,-44,-12,20,23,8,6,-63,-14,4,7,11,0,0,-1,11,-72,4,-5,-7,-3,-10,-5,-1,-11,-81,-17,-5,-16,-85,-4,-18,-17,-4,-14,-26,-10,-93,-12,-26,-23,-19,-30,-30,-31,-19,-102,-26,-35,-37,-33,-40,-35,-31,-41,-97,3348,3356,0,3252,0,3922,3771,7,76,108,102,104,86,91,88,48,36,55,51,-19,46,58,66,46,59,-25,48,58,55,55,-30,36,47,45,50,30,37,41,-38,38,39,41,27,-43,22,34,42,22,35,-35,-50,-51,-2,16,13,30,26,26,15,27,9,15,27,-49,3412,3421,0,3478,3714,0,3124,8,64,102,98,100,88,88,85,92,56,27,54,51,42,51,49,39,-31,51,36,35,42,47,-37,46,40,-40,31,23,43,25,-45,30,22,22,35,-50,22,32,-53,25,23,-56,27,14,10,-60,-22,11,2,14,19,-66,-28,14,4,-2,-71,11,-4,10,9,-3,1,-7,-65,3485,3493,0,3645,0,3405,3570,7,65,89,99,98,108,85,108,76,8,27,27,36,-48,16,32,18,13,-53,18,10,27,-57,8,10,9,17,-62,16,16,19,7,10,5,21,-1,-3,-72,-3,5,7,-76,6,1,-2,-11,3,-10,-10,-6,-14,-59,-87,1,-10,-5,-84,-10,-24,-94,-21,-11,-14,-14,-99,-22,-22,-18,-103,-23,-20,-33,-23,-39,-109,-27,-26,-30,-44,-114,-28,-44,-52,-34,-105,3577,3589,0,0,3478,4218,4289,11,72,87,92,87,95,83,84,14,57,77,77,55,34,55,60,-26,56,41,40,-30,38,54,40,34,34,42,30,31,-39,32,28,40,26,-44,34,24,-47,32,33,29,33,27,31,35,25,13,-57,22,20,16,28,15,6,18,-65,2,2,15,4,1,7,-72,14,5,7,-1,-63,3652,3673,0,0,0,3478,0,20,51,84,80,93,8,62,88,70,84,83,75,79,71,-1,33,66,74,79,63,75,40,32,70,77,-11,57,63,69,54,-16,51,61,-19,69,58,63,-23,63,57,39,53,-28,51,52,38,51,36,44,49,47,-37,41,39,-40,43,30,26,-44,26,33,-16,3721,3735,0,3880,0,0,3405,13,54,100,86,103,15,63,98,77,93,94,78,90,90,35,49,68,64,-6,59,61,59,73,-11,53,69,55,-15,49,59,58,-19,64,58,57,-23,59,52,39,49,48,-29,40,48,50,-33,55,44,49,-23,3778,3786,0,4122,3341,0,0,7,76,108,88,88,97,89,102,34,48,66,69,73,62,62,61,73,3,72,61,77,55,53,-2,-17,34,53,49,68,-15,59,45,-25,39,49,48,-29,39,46,48,51,55,-21,3828,3851,0,0,0,3124,0,22,50,88,92,7,41,77,83,70,81,77,65,83,67,-3,34,74,79,71,76,56,63,67,28,55,82,79,70,72,78,85,9,-4,68,78,0,75,-9,73,73,61,63,62,-15,71,62,64,56,53,57,49,-9,3887,3895,0,0,0,3714,3977,7,68,97,107,89,93,89,97,26,43,91,73,85,91,85,72,72,76,68,3,78,-6,63,74,60,59,79,57,0,54,67,57,52,50,-5,3929,3936,0,3341,4057,0,0,6,59,107,91,88,90,90,40,38,70,68,58,-12,66,56,-15,68,55,51,-19,47,44,44,50,54,44,58,56,-28,54,39,38,45,-33,50,44,-36,35,27,47,29,-41,38,36,43,24,36,-33,3984,3996,0,0,3880,0,0,11,68,86,102,87,99,102,80,98,92,94,100,60,24,43,39,51,37,-33,31,47,33,-37,27,-39,30,28,45,-43,40,24,30,22,35,18,29,29,17,30,-27,-55,28,15,11,30,-53,21,7,-63,1,11,10,-67,-2,10,6,13,-3,-5,-74,-7,3,10,0,-67,-80,3,-10,-4,1,-14,-14,-73,4064,4087,0,0,0,0,3922,22,65,74,90,87,6,41,86,76,88,70,0,44,63,70,74,79,63,71,57,69,57,58,34,39,81,-4,60,74,73,61,56,72,72,-12,71,65,-15,50,52,-18,68,59,61,53,50,54,46,-26,51,51,53,47,34,44,43,55,-21,4129,4140,0,4385,0,3771,0,10,68,86,106,92,89,82,100,88,93,91,77,6,38,18,36,36,33,-25,-52,-2,30,27,9,21,10,10,8,-47,-62,-15,12,4,-1,16,1,-69,13,14,8,7,2,14,-76,0,-9,-14,3,4,0,-14,-7,-16,-8,-3,-5,-89,-20,-9,-13,-16,-94,-25,-23,-27,-14,-10,-100,-18,-18,-38,-22,-22,-106,-23,-29,-109,-28,-42,-45,-48,-38,-42,-50,-35,-53,-35,-51,-107,4225,4237,0,3570,0,0,0,11,58,98,90,91,95,85,84,96,86,90,82,51,38,59,64,-22,60,45,44,-26,38,-28,58,42,42,52,36,32,44,29,45,30,-39,47,32,42,29,-44,35,30,18,30,34,-50,19,27,29,-54,-4,24,25,15,19,11,7,20,16,9,3,-66,19,-50,-55,4296,4305,0,0,3570,0,0,8,59,102,104,103,93,87,97,99,79,5,24,20,-50,26,17,31,11,21,-56,30,7,17,16,22,-62,2,14,3,-66,17,4,0,-70,6,-3,11,-9,1,-76,-7,-2,0,-1,1,-82,-18,-2,-16,-86,-4,-12,-16,-19,-19,-8,-17,-5,-95,-28,-24,-28,-29,-31,-19,-33,-25,-20,-105,-39,-28,-32,-30,-28,-28,-98,-113,-67,-33,-116,-52,-36,-50,-120,-37,-50,-54,-35,-94,4392,4401,0,4457,0,4122,0,8,72,88,105,104,85,90,87,100,55,29,48,44,63,-20,54,40,-30,34,-32,43,39,49,48,39,31,-39,44,46,31,40,40,44,-46,18,30,19,-50,32,32,12,28,29,17,21,13,-59,24,18,-62,13,15,14,9,-67,-3,7,6,-71,-7,3,-1,0,-7,-63,4464,4484,0,0,4556,4385,0,19,64,81,78,95,91,81,91,95,5,39,75,71,68,75,79,77,70,74,79,71,2,38,-41,42,29,25,-45,32,22,40,35,-50,31,27,26,23,-43,-56,8,-58,21,22,8,21,20,21,17,3,-54,15,0,8,12,1,11,-1,11,-7,-77,-8,-3,-1,-2,0,-83,3,-12,-10,-11,-88,-3,-21,-9,-19,-23,-5,-95,-7,-18,-13,-17,-100,-28,-34,-34,-26,-21,-33,-23,-19,-95,4563,4588,1553,0,0,0,4457,24,56,89,75,88,87,88,84,70,13,50,67,75,79,68,78,66,78,60,-10,27,64,66,65,67,12,53,97,83,93,105,105,87,91,83,25,24,23,4122,4653,131099,0,4057,4662,28,1829,3405,4676,2147483677,0,4289,4684,8222,0,3821,4704,31,1818,4218,4724,524320,0,3252,4733,33,1872,3771,4741,34,1850,3714,4753,547,0,3645,4762,134217764,0,4385,4771,37,1796,3977,4782,1062,0,3922,4794,55,0,8,101,102,100,100,96,92,102,89,13,92,96,87,89,93,87,97,81,11,86,88,87,87,7,90,102,107,91,99,98,84,19,78,95,95,92,88,86,72,91,89,4,76,69,70,0,66,80,66,61,72,19,84,85,76,88,93,8,76,82,74,71,87,84,80,77,64,69,75,65,79,8,96,102,98,100,91,101,83,94,7,105,96,102,106,100,98,102,11,98,99,95,102,86,94,15,90,78,98,76,8,103,105,100,86,97,88,96,101,8,89,106,106,90,102,92,101,92,10,91,104,87,84,98,86,16,95,93,81,11,91,93,107,87,85,16,95,93,86,90,95,11,89,85,101,93,17,93,80,98,97,81,93