From b168df78cdecd655e757def6c6070712d0989e12 Mon Sep 17 00:00:00 2001 From: Andrea Bellandi Date: Sun, 9 Aug 2015 20:55:40 +0200 Subject: [PATCH 01/11] completed Strategy0 refactoring --- src/Mainpf.hs | 9 +++-- src/Strategy0.hs | 90 +++++++++++++++++++++++++++++------------- src/StrategyManager.hs | 26 ++++++------ 3 files changed, 82 insertions(+), 43 deletions(-) diff --git a/src/Mainpf.hs b/src/Mainpf.hs index 6b707c9..bbaa0bc 100644 --- a/src/Mainpf.hs +++ b/src/Mainpf.hs @@ -15,6 +15,7 @@ import Data.Aeson import Data.Maybe import StrategyManager +import Strategy0 import Datatypes import Datatypes.Game import VM @@ -32,7 +33,7 @@ timelimitratio = 0.9 memlimitratio :: Double memlimitratio = 0.9 gccompperstep :: Integer -gccompperstep = 10 +gccompperstep = 100000 data JSONSer = JSONSer { problemId :: Int, @@ -48,8 +49,10 @@ type Id = Int type Seed = Int strategies :: Game -> StdGen -> Maybe [Command] -> GameComputation -strategies g sgen cmd = [MkStrategyWrapper (initst g sgen cmd :: NullStrategy1), - MkStrategyWrapper (initst g sgen cmd :: NullStrategy2)] +strategies g sgen cmd = [MkStrategyWrapper (initst g sgen cmd :: Strategy0)] + +-- = [MkStrategyWrapper (initst g sgen cmd :: NullStrategy1), +-- MkStrategyWrapper (initst g sgen cmd :: NullStrategy2)] -- example :: -- = [MkStrategyWrapper (init g sgen cmd :: Strat0), diff --git a/src/Strategy0.hs b/src/Strategy0.hs index b6f8e41..0424331 100644 --- a/src/Strategy0.hs +++ b/src/Strategy0.hs @@ -1,36 +1,61 @@ -module Strategy0 where +module Strategy0(Strategy0) where import qualified Data.PQueue.Prio.Max as PQ +import System.Random(StdGen) import Data.Maybe (isJust) - import Datatypes import Datatypes.Game (Command(..)) import qualified Datatypes.Game as Game import VM +import StrategyManager + commandsList :: [Command] commandsList = [MoveSE, MoveSW, MoveW, MoveE, RotateClockwise, RotateCounterclockwise] type Queue = PQ.MaxPQueue Int Game +data Strategy0 = Strategy0 (Queue, [Game]) + + +instance Strategy Strategy0 where + initst = strategy0initst + advance = strategy0advance + getbest = strategy0getbest + +strategy0initst :: Game -> StdGen -> Maybe [Command] -> Strategy0 +strategy0initst game _ _ = (Strategy0 (PQ.singleton (fullScore game) game, [])) + +strategy0advance :: Strategy0 -> Either Strategy0 ([Command],Int) +strategy0advance (Strategy0 (queue,completed)) = let candidates = map (step game) commandsList + (newQueue, newCompleted) = updateCollections candidates remQueue (game:completed) + in Left (Strategy0 (newQueue, newCompleted)) + where + ((score, game), remQueue) = PQ.deleteFindMax queue + updateCollections [] q l = (q, l) + updateCollections ((g, n):rs) q l = case n of + OK -> updateCollections rs (pushToQueue q g) l + Lock _ -> updateCollections rs (pushToQueue q g) l + GameOver -> updateCollections rs q (pushToList l g) + _ -> updateCollections rs q l + pushToQueue q x = PQ.insert (fullScore x) x q + pushToList c x = x : c + +strategy0getbest :: Strategy0 -> ([Command], Int) +strategy0getbest (Strategy0 (incomplete,completed)) = let (_, bestIncomplete) = PQ.findMax incomplete + resultGame = findListMax (bestIncomplete:completed) + in (reverse (Game.history resultGame), fullScore resultGame) + fullScore :: Game -> Int fullScore game = Game.score game + (Game.cacheToScore $ Game.phrasesCache game) -strat0 :: Game -> ([Command],Int) -strat0 game = let firstQueue = PQ.singleton (fullScore game) game - (incomplete, completed) = findBest maxIter firstQueue [] - (_, bestIncomplete) = PQ.findMax incomplete - resultGame = findListMax (bestIncomplete:completed) - in (reverse (Game.history resultGame), fullScore resultGame) - where - maxIter = 50000 - findListMax :: [Game] -> Game findListMax (x:xs) = innerFindListMax x xs where innerFindListMax currentMax [] = currentMax innerFindListMax currentMax (y:ys) = innerFindListMax (if (fullScore currentMax) > (fullScore y) then currentMax else y) ys + partition :: (a -> Bool) -> [a] -> ([a], [a]) partition p items = innerPartition items [] [] where innerPartition [] ts fs = (ts, fs) @@ -55,19 +80,30 @@ tryPowerPhrases game = validResults where Lock _ -> innerExpand nn ps _ -> Nothing -findBest :: Int -> Queue -> [Game] -> (Queue, [Game]) -findBest 0 queue completed = (queue, completed) -findBest i queue completed = - let candidates = map (step game) commandsList -- ++ (tryPowerPhrases game) - (newQueue, newCompleted) = updateCollections candidates remQueue (game:completed) - in findBest (i - 1) newQueue newCompleted - where - ((score, game), remQueue) = PQ.deleteFindMax queue - updateCollections [] q l = (q, l) - updateCollections ((g, n):rs) q l = case n of - OK -> updateCollections rs (pushToQueue q g) l - Lock _ -> updateCollections rs (pushToQueue q g) l - GameOver -> updateCollections rs q (pushToList l g) - _ -> updateCollections rs q l - pushToQueue q x = PQ.insert (fullScore x) x q - pushToList c x = x : c +-- +-- Old Strategy0 Code +-- +-- findBest :: Int -> Queue -> [Game] -> (Queue, [Game]) +-- findBest 0 queue completed = (queue, completed) +-- findBest i queue completed = let candidates = map (step game) commandsList ++ (tryPowerPhrases game) +-- (newQueue, newCompleted) = updateCollections candidates remQueue (game:completed) +-- in findBest (i - 1) newQueue newCompleted +-- where +-- ((score, game), remQueue) = PQ.deleteFindMax queue +-- updateCollections [] q l = (q, l) +-- updateCollections ((g, n):rs) q l = case n of +-- OK -> updateCollections rs (pushToQueue q g) l +-- Lock _ -> updateCollections rs (pushToQueue q g) l +-- GameOver -> updateCollections rs q (pushToList l g) +-- _ -> updateCollections rs q l +-- pushToQueue q x = PQ.insert (fullScore x) x q + +-- strat0 :: Game -> ([Command],Int) +-- strat0 game = let firstQueue = PQ.singleton (fullScore game) game +-- (incomplete, completed) = findBest maxIter firstQueue [] +-- (_, bestIncomplete) = PQ.findMax incomplete +-- resultGame = findListMax (bestIncomplete:completed) +-- in (reverse (Game.history resultGame), fullScore resultGame) +-- where +-- maxIter = 50000 +-- pushToList c x = x : c diff --git a/src/StrategyManager.hs b/src/StrategyManager.hs index c6b661a..f9583d9 100644 --- a/src/StrategyManager.hs +++ b/src/StrategyManager.hs @@ -15,19 +15,6 @@ data StrategyWrapper = forall a . Strategy a => MkStrategyWrapper a data NullStrategy1 = NullS1 -instance Strategy NullStrategy1 where - initst _ _ _ = NullS1 - advance _ = Left NullS1 - getbest _ = ([],0) - - -data NullStrategy2 = NullS2 - -instance Strategy NullStrategy2 where - initst _ _ _ = NullS2 - advance _ = Left NullS2 - getbest _ = ([],0) - initWrapper :: Strategy a => a -> StrategyWrapper @@ -69,3 +56,16 @@ getBestGameComputation gc = foldl bestgame (([], 0), 0) (map getbestWrapper gc) advanceGameComputation :: GameComputation -> GameComputation advanceGameComputation gc = map advanceWrapper gc +instance Strategy NullStrategy1 where + initst _ _ _ = NullS1 + advance _ = Left NullS1 + getbest _ = ([],0) + + +data NullStrategy2 = NullS2 + +instance Strategy NullStrategy2 where + initst _ _ _ = NullS2 + advance _ = Left NullS2 + getbest _ = ([],0) + From 0a80fe2b077012d606a425e14d52c5511060fad3 Mon Sep 17 00:00:00 2001 From: Andrea Bellandi Date: Sun, 9 Aug 2015 22:23:06 +0200 Subject: [PATCH 02/11] broken Main.hs --- icfp2015.cabal | 4 ++-- src/{Mainpf.hs => Main.hs} | 14 +++++++------- 2 files changed, 9 insertions(+), 9 deletions(-) rename src/{Mainpf.hs => Main.hs} (97%) diff --git a/icfp2015.cabal b/icfp2015.cabal index 734a37d..7c61263 100644 --- a/icfp2015.cabal +++ b/icfp2015.cabal @@ -51,7 +51,7 @@ cabal-version: >=1.10 executable icfp2015 -- .hs or .lhs file containing the Main module. - main-is: Main0.hs + main-is: Main.hs -- Modules included in this executable, other than Main. other-modules: Datatypes, Datatypes.Board, Datatypes.Cell, Datatypes.Game, Datatypes.Unit @@ -60,7 +60,7 @@ executable icfp2015 other-extensions: OverloadedStrings, DeriveGeneric, DeriveDataTypeable -- Other library packages from which modules are imported. - build-depends: base >=4.6 && <4.9, hashable >=1.2 && <1.3, containers >=0.5 && <0.6, QuickCheck >=2.7 && <2.9, bytestring >=0.10 && <0.11, aeson >=0.8 && <0.9, pqueue >=1.3 && <1.4, clock >= 0.1 + build-depends: base >=4.6 && <4.9, hashable >=1.2 && <1.3, containers >=0.5 && <0.6, QuickCheck >=2.7 && <2.9, bytestring >=0.10 && <0.11, aeson >=0.8 && <0.9, pqueue >=1.3 && <1.4, clock, random -- Directories containing source files. hs-source-dirs: src diff --git a/src/Mainpf.hs b/src/Main.hs similarity index 97% rename from src/Mainpf.hs rename to src/Main.hs index bbaa0bc..8597033 100644 --- a/src/Mainpf.hs +++ b/src/Main.hs @@ -2,7 +2,7 @@ {-# LANGUAGE ExistentialQuantification #-} {-# OPTIONS -Wall #-} -module Mainf where +module Main where import Data.Int import Data.List @@ -29,11 +29,11 @@ logfilename :: String logfilename = "scores" timelimitratio :: Double -timelimitratio = 0.9 +timelimitratio = 1.0 memlimitratio :: Double -memlimitratio = 0.9 +memlimitratio = 1.0 gccompperstep :: Integer -gccompperstep = 100000 +gccompperstep = 100 data JSONSer = JSONSer { problemId :: Int, @@ -49,7 +49,7 @@ type Id = Int type Seed = Int strategies :: Game -> StdGen -> Maybe [Command] -> GameComputation -strategies g sgen cmd = [MkStrategyWrapper (initst g sgen cmd :: Strategy0)] +strategies g sgen cmd = [MkStrategyWrapper (initst g sgen cmd :: NullStrategy1)] -- = [MkStrategyWrapper (initst g sgen cmd :: NullStrategy1), -- MkStrategyWrapper (initst g sgen cmd :: NullStrategy2)] @@ -73,6 +73,7 @@ main = do args <- getArgs let (ids,seeds,gamecomputations) = unzip3 loaddata inittime <- secTime results <- iterategc gamecomputations (timestruct timelimit inittime) memlimit + putStrLn "lol" let (commandswpoints,strat) = unzip results let (commandlists, points) = unzip commandswpoints let wordlists = map cmdToString commandlists @@ -118,8 +119,7 @@ iterategc gcs tlimit mlimit = do rtl <- timeLimit tlimit applyNtimes 1 f x = f x applyNtimes n f x = f (applyNtimes (n-1) f x) best = map getBestGameComputation gcs - - + timeLimit :: Maybe (Int,Int64) -> IO Bool timeLimit Nothing = return False timeLimit (Just (itime,limit)) = do atime <- secTime From af00345e0083b7087bf57788a68fb7f694226589 Mon Sep 17 00:00:00 2001 From: Andrea Bellandi Date: Sun, 9 Aug 2015 22:45:24 +0200 Subject: [PATCH 03/11] push version --- src/Main.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 8597033..e261822 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE BangPatterns #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE ExistentialQuantification #-} {-# OPTIONS -Wall #-} @@ -49,7 +50,7 @@ type Id = Int type Seed = Int strategies :: Game -> StdGen -> Maybe [Command] -> GameComputation -strategies g sgen cmd = [MkStrategyWrapper (initst g sgen cmd :: NullStrategy1)] +strategies g sgen cmd = [MkStrategyWrapper (initst g sgen cmd :: Strategy0)] -- = [MkStrategyWrapper (initst g sgen cmd :: NullStrategy1), -- MkStrategyWrapper (initst g sgen cmd :: NullStrategy2)] @@ -106,8 +107,8 @@ readFiles (x:xs) = do f <- BS.readFile x iterategc :: [GameComputation] -> Maybe (Int,Int64) -> Maybe Int -> IO [(([Command], Int), Int)] iterategc gcs tlimit mlimit = do rtl <- timeLimit tlimit - rml <- memLimit mlimit - (gcresult rtl rml) + rml <- memLimit mlimit + (gcresult rtl rml) where gcresult True _ = return best gcresult _ True = return best From 623b94df5014b8a363ed51d1a878fbdffee68d71 Mon Sep 17 00:00:00 2001 From: Slash Date: Sun, 9 Aug 2015 23:13:10 +0200 Subject: [PATCH 04/11] tail recursion fix --- src/Main.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index e261822..cefcad5 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -107,8 +107,8 @@ readFiles (x:xs) = do f <- BS.readFile x iterategc :: [GameComputation] -> Maybe (Int,Int64) -> Maybe Int -> IO [(([Command], Int), Int)] iterategc gcs tlimit mlimit = do rtl <- timeLimit tlimit - rml <- memLimit mlimit - (gcresult rtl rml) + rml <- memLimit mlimit + (gcresult rtl rml) where gcresult True _ = return best gcresult _ True = return best @@ -116,9 +116,9 @@ iterategc gcs tlimit mlimit = do rtl <- timeLimit tlimit then return best else iterategc (applyNtimes gccompperstep itf gcs) tlimit mlimit where - itf gcs1 = map (\x -> advanceGameComputation x) gcs1 - applyNtimes 1 f x = f x - applyNtimes n f x = f (applyNtimes (n-1) f x) + itf gcs1 = map advanceGameComputation gcs1 + applyNtimes 0 _ accum = accum + applyNtimes n f accum = applyNtimes (n - 1) f (f accum) best = map getBestGameComputation gcs timeLimit :: Maybe (Int,Int64) -> IO Bool From 26b59c0a9a61e9f53a989c2fdbba7ee764f4ab0f Mon Sep 17 00:00:00 2001 From: Slash Date: Mon, 10 Aug 2015 00:22:53 +0200 Subject: [PATCH 05/11] deepseq awesomeness --- src/Main.hs | 54 ++++++++++++++++++++++++++++++----------------------- 1 file changed, 31 insertions(+), 23 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index cefcad5..c8a0de2 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -5,8 +5,9 @@ module Main where +import Control.DeepSeq (deepseq, NFData(..)) import Data.Int -import Data.List +import Data.List (zip4) import qualified Data.ByteString.Lazy.Char8 as BS import System.Environment import System.Random @@ -24,15 +25,20 @@ import Opt import JSONDeser(readInput) import PowerPhrases -ptag :: String -ptag = "lilik0" -logfilename :: String -logfilename = "scores" +import Debug.Trace (trace) + +strategyTag :: String +strategyTag = "lilik0" + +logFileName :: String +logFileName = "scores" + +timeLimitRatio :: Double +timeLimitRatio = 1.0 + +memLimitRatio :: Double +memLimitRatio = 1.0 -timelimitratio :: Double -timelimitratio = 1.0 -memlimitratio :: Double -memlimitratio = 1.0 gccompperstep :: Integer gccompperstep = 100 @@ -78,7 +84,7 @@ main = do args <- getArgs let (commandswpoints,strat) = unzip results let (commandlists, points) = unzip commandswpoints let wordlists = map cmdToString commandlists - let outJSONstructs = zipWith3 (\x y z -> (JSONSer x y ptag z)) ids seeds wordlists + let outJSONstructs = zipWith3 (\x y z -> (JSONSer x y strategyTag z)) ids seeds wordlists BS.putStrLn $ encode outJSONstructs writelogfile logf (zip4 ids seeds points strat) where @@ -105,27 +111,29 @@ readFiles (x:xs) = do f <- BS.readFile x fs <- readFiles xs return (f:fs) +instance NFData Command where rnf x = seq x () + iterategc :: [GameComputation] -> Maybe (Int,Int64) -> Maybe Int -> IO [(([Command], Int), Int)] iterategc gcs tlimit mlimit = do rtl <- timeLimit tlimit rml <- memLimit mlimit - (gcresult rtl rml) + if rtl || rml + then return best + else if (and $ map finishedGameComputation gcs) + then return best + else let mona = (applyNtimes gccompperstep itf gcs) + mona1 = map getBestGameComputation gcs + in mona1 `deepseq` (iterategc mona tlimit mlimit) where - gcresult True _ = return best - gcresult _ True = return best - gcresult _ _ = if (and $ map finishedGameComputation gcs) - then return best - else iterategc (applyNtimes gccompperstep itf gcs) tlimit mlimit - where - itf gcs1 = map advanceGameComputation gcs1 - applyNtimes 0 _ accum = accum - applyNtimes n f accum = applyNtimes (n - 1) f (f accum) - best = map getBestGameComputation gcs + itf gcs1 = map advanceGameComputation gcs1 + applyNtimes 0 _ accum = accum + applyNtimes n f accum = applyNtimes (n - 1) f (f accum) + best = map getBestGameComputation gcs timeLimit :: Maybe (Int,Int64) -> IO Bool timeLimit Nothing = return False timeLimit (Just (itime,limit)) = do atime <- secTime let diff = (atime - (fromIntegral itime)) - return (((fromIntegral limit) * timelimitratio) < (fromIntegral diff)) + return (((fromIntegral limit) * timeLimitRatio) < (fromIntegral diff)) memLimit :: Maybe Int -> IO Bool @@ -137,7 +145,7 @@ secTime = do (TimeSpec s _) <- getTime Monotonic writelogfile :: Bool -> [(Int,Int,Int,Int)] -> IO () writelogfile False _ = return () -writelogfile _ els = writeFile logfilename scoredata +writelogfile _ els = writeFile logFileName scoredata where scoredata = foldl strlog "\n" els strlog x (a,b,c,d) = sa ++ sb ++ sc ++ sd ++ x ++ "\n" From 1d849d6fb1ddd4dbc099eb03266066eeb8a58535 Mon Sep 17 00:00:00 2001 From: Slash Date: Mon, 10 Aug 2015 00:40:41 +0200 Subject: [PATCH 06/11] added deepseq dependency, fixes --- icfp2015.cabal | 2 +- src/Main.hs | 9 ++++----- 2 files changed, 5 insertions(+), 6 deletions(-) diff --git a/icfp2015.cabal b/icfp2015.cabal index 7c61263..175bb83 100644 --- a/icfp2015.cabal +++ b/icfp2015.cabal @@ -60,7 +60,7 @@ executable icfp2015 other-extensions: OverloadedStrings, DeriveGeneric, DeriveDataTypeable -- Other library packages from which modules are imported. - build-depends: base >=4.6 && <4.9, hashable >=1.2 && <1.3, containers >=0.5 && <0.6, QuickCheck >=2.7 && <2.9, bytestring >=0.10 && <0.11, aeson >=0.8 && <0.9, pqueue >=1.3 && <1.4, clock, random + build-depends: base >=4.6 && <4.9, hashable >=1.2 && <1.3, containers >=0.5 && <0.6, QuickCheck >=2.7 && <2.9, bytestring >=0.10 && <0.11, aeson >=0.8 && <0.9, pqueue >=1.3 && <1.4, clock, random, deepseq >= 1.3 && <1.4 -- Directories containing source files. hs-source-dirs: src diff --git a/src/Main.hs b/src/Main.hs index c8a0de2..10e2d3d 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -80,13 +80,12 @@ main = do args <- getArgs let (ids,seeds,gamecomputations) = unzip3 loaddata inittime <- secTime results <- iterategc gamecomputations (timestruct timelimit inittime) memlimit - putStrLn "lol" let (commandswpoints,strat) = unzip results let (commandlists, points) = unzip commandswpoints let wordlists = map cmdToString commandlists let outJSONstructs = zipWith3 (\x y z -> (JSONSer x y strategyTag z)) ids seeds wordlists BS.putStrLn $ encode outJSONstructs - writelogfile logf (zip4 ids seeds points strat) + writeLogFile logf (zip4 ids seeds points strat) where timestruct Nothing _ = Nothing timestruct (Just maxtime) intime = Just (maxtime, intime) @@ -143,9 +142,9 @@ secTime :: IO Int64 secTime = do (TimeSpec s _) <- getTime Monotonic return s -writelogfile :: Bool -> [(Int,Int,Int,Int)] -> IO () -writelogfile False _ = return () -writelogfile _ els = writeFile logFileName scoredata +writeLogFile :: Bool -> [(Int,Int,Int,Int)] -> IO () +writeLogFile False _ = return () +writeLogFile _ els = writeFile logFileName scoredata where scoredata = foldl strlog "\n" els strlog x (a,b,c,d) = sa ++ sb ++ sc ++ sd ++ x ++ "\n" From 787cc8789c42750d3ffed2743e2d594b665a51c3 Mon Sep 17 00:00:00 2001 From: Andrea Bellandi Date: Mon, 10 Aug 2015 00:50:39 +0200 Subject: [PATCH 07/11] removed some dependencies --- src/JSONDeser.hs | 6 +++--- src/LCG.hs | 2 +- src/Main.hs | 2 +- src/PowerPhrases.hs | 10 +++++----- src/StrategyManager.hs | 8 +++----- 5 files changed, 13 insertions(+), 15 deletions(-) diff --git a/src/JSONDeser.hs b/src/JSONDeser.hs index b85fded..353e8a9 100644 --- a/src/JSONDeser.hs +++ b/src/JSONDeser.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveGeneric #-} module JSONDeser where -import qualified Data.Set as Set +import Data.Set(fromList) import Data.Maybe import qualified Data.ByteString.Lazy as BS import Data.Aeson @@ -52,10 +52,10 @@ newGame :: Input -> (Int,[(Int,DT.Game)]) newGame input = (JSONDeser.id input, zip (sourceSeeds input) (map gameFromSeed (sourceSeeds input))) where gameFromSeed seed = DT.Game.new board (seedUnits seed input) - board = DT.Board w h filledel + board = DT.Board w h filledelement w = width input h = height input - filledel = Set.fromList (map cellConvVM (filled input)) + filledelement = Set.fromList (map cellConvVM (filled input)) seedUnits :: Int -> Input -> [DT.Unit] seedUnits s input = map (\x -> uinput !! x ) unit_index diff --git a/src/LCG.hs b/src/LCG.hs index 98a413d..ea005dc 100644 --- a/src/LCG.hs +++ b/src/LCG.hs @@ -1,6 +1,6 @@ module LCG where -import Data.Bits +import Data.Bits(shiftR,(.&.)) modulus = 2^32 multiplier = 1103515245 diff --git a/src/Main.hs b/src/Main.hs index cefcad5..337f7c0 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -50,7 +50,7 @@ type Id = Int type Seed = Int strategies :: Game -> StdGen -> Maybe [Command] -> GameComputation -strategies g sgen cmd = [MkStrategyWrapper (initst g sgen cmd :: Strategy0)] +strategies g sgen cmd = [MkStrategyWrapper (initst g sgen cmd :: NullStrategy1)] -- = [MkStrategyWrapper (initst g sgen cmd :: NullStrategy1), -- MkStrategyWrapper (initst g sgen cmd :: NullStrategy2)] diff --git a/src/PowerPhrases.hs b/src/PowerPhrases.hs index 94ac0d7..6c59930 100644 --- a/src/PowerPhrases.hs +++ b/src/PowerPhrases.hs @@ -1,8 +1,11 @@ +{-# OPTIONS -Wall #-} module PowerPhrases where -import Data.Maybe +import Data.Maybe(mapMaybe) import Datatypes.Game (Command(..)) +listToCommand :: String -> [Command] +listToCommand str = mapMaybe charToCommand str charToCommand :: Char -> Maybe Command @@ -48,8 +51,5 @@ charToCommand 'u' = Just RotateCounterclockwise charToCommand 'w' = Just RotateCounterclockwise charToCommand 'x' = Just RotateCounterclockwise -charToCommand '\t' = Nothing -charToCommand '\n' = Nothing -charToCommand '\r' = Nothing - +charToCommand _ = Nothing diff --git a/src/StrategyManager.hs b/src/StrategyManager.hs index f9583d9..915d779 100644 --- a/src/StrategyManager.hs +++ b/src/StrategyManager.hs @@ -2,16 +2,14 @@ {-# OPTIONS -Wall #-} module StrategyManager where -import System.Random - -import Datatypes -import Datatypes.Game +import System.Random(StdGen) +import Datatypes.Game(Game,Command) type GameComputation = [StrategyWrapper] data StrategyWrapper = forall a . Strategy a => MkStrategyWrapper a | FinishedGame ([Command], Int) - + data NullStrategy1 = NullS1 From c5926314c6b9a11bf41762addeb2db7c5ece4da6 Mon Sep 17 00:00:00 2001 From: Andrea Bellandi Date: Mon, 10 Aug 2015 04:19:47 +0200 Subject: [PATCH 08/11] resolved time bug cleaned Main --- src/JSONDeser.hs | 4 +- src/Main.hs | 125 +++++++++++++++++++++-------------------- src/StrategyManager.hs | 23 +++++--- 3 files changed, 82 insertions(+), 70 deletions(-) diff --git a/src/JSONDeser.hs b/src/JSONDeser.hs index 353e8a9..8ffff2b 100644 --- a/src/JSONDeser.hs +++ b/src/JSONDeser.hs @@ -55,7 +55,7 @@ newGame input = (JSONDeser.id input, zip (sourceSeeds input) (map gameFromSeed ( board = DT.Board w h filledelement w = width input h = height input - filledelement = Set.fromList (map cellConvVM (filled input)) + filledelement = fromList (map cellConvVM (filled input)) seedUnits :: Int -> Input -> [DT.Unit] seedUnits s input = map (\x -> uinput !! x ) unit_index @@ -69,5 +69,5 @@ cellConvVM (Cell x y) = (x,y) unitConvVM :: Unit -> DT.Unit unitConvVM unit = DT.Unit (cellConvVM (pivot unit)) setcell where - setcell = Set.fromList (map cellConvVM (members unit)) + setcell = fromList (map cellConvVM (members unit)) diff --git a/src/Main.hs b/src/Main.hs index e6823d0..0042480 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -7,7 +7,6 @@ module Main where import Control.DeepSeq (deepseq, NFData(..)) import Data.Int -import Data.List (zip4) import qualified Data.ByteString.Lazy.Char8 as BS import System.Environment import System.Random @@ -18,15 +17,12 @@ import Data.Maybe import StrategyManager import Strategy0 -import Datatypes -import Datatypes.Game +import Datatypes.Game(Game,Command) import VM import Opt import JSONDeser(readInput) import PowerPhrases -import Debug.Trace (trace) - strategyTag :: String strategyTag = "lilik0" @@ -34,19 +30,19 @@ logFileName :: String logFileName = "scores" timeLimitRatio :: Double -timeLimitRatio = 1.0 +timeLimitRatio = 0.96 memLimitRatio :: Double memLimitRatio = 1.0 -gccompperstep :: Integer -gccompperstep = 100 +computationsPerStep :: Int +computationsPerStep = 10 data JSONSer = JSONSer { problemId :: Int, - seed :: Int, - tag :: String, - solution :: String + problemSeed :: Int, + problemTag :: String, + problemSolution :: String } deriving (Show, Generic) instance FromJSON JSONSer @@ -55,8 +51,9 @@ instance ToJSON JSONSer type Id = Int type Seed = Int + strategies :: Game -> StdGen -> Maybe [Command] -> GameComputation -strategies g sgen cmd = [MkStrategyWrapper (initst g sgen cmd :: NullStrategy1)] +strategies g sgen cmd = [MkStrategyWrapper (initst g sgen cmd :: Strategy0)] -- = [MkStrategyWrapper (initst g sgen cmd :: NullStrategy1), -- MkStrategyWrapper (initst g sgen cmd :: NullStrategy2)] @@ -67,42 +64,44 @@ strategies g sgen cmd = [MkStrategyWrapper (initst g sgen cmd :: NullStrategy1)] -- MkStrategyWrapper (init g sgen cmd :: Strat2)] main :: IO () -main = do args <- getArgs +main = do initTime <- secTime + args <- getArgs opt <- parseArgs args - let files = optFile opt - let timelimit = optTime opt - let memlimit = optMem opt - let powerp = optPowerPhrase opt - let cores = optCores opt - let logf = optLog opt + let files = optFile opt + let maxTime = optTime opt + let maxMem = optMem opt + let powerPhrase = optPowerPhrase opt + let logFile = optLog opt rng <- getStdGen - loaddata <- createComputationsFromFiles files rng powerp - let (ids,seeds,gamecomputations) = unzip3 loaddata - inittime <- secTime - results <- iterategc gamecomputations (timestruct timelimit inittime) memlimit - let (commandswpoints,strat) = unzip results - let (commandlists, points) = unzip commandswpoints - let wordlists = map cmdToString commandlists - let outJSONstructs = zipWith3 (\x y z -> (JSONSer x y strategyTag z)) ids seeds wordlists + initialData <- createComputationsFromFiles files rng powerPhrase + let (_, _,gameComputations) = unzip3 initialData + commandResults <- iterateGame gameComputations (timeStruct maxTime initTime) maxMem + let stringResults = map (\(cmds,score,algoIdx) -> (cmdToString cmds,score,algoIdx)) commandResults + let outJSONstructs = zipWith jsonBuilder initialData stringResults BS.putStrLn $ encode outJSONstructs - writeLogFile logf (zip4 ids seeds points strat) + writeLogFile logFile (zipWith logFileBuilder initialData stringResults) where - timestruct Nothing _ = Nothing - timestruct (Just maxtime) intime = Just (maxtime, intime) - + timeStruct Nothing _ = Nothing + timeStruct (Just stopTime) initialTime = Just (fromIntegral stopTime,fromIntegral initialTime) + + + + jsonBuilder (idx, seed, _) (strCmds, _, _) = (JSONSer idx seed strategyTag strCmds) + logFileBuilder (idx, seed, _) (_ ,score , algoIdx) = (idx, seed, score, algoIdx) + createComputationsFromFiles :: [String] -> StdGen -> Maybe String -> IO [(Id,Seed,GameComputation)] -createComputationsFromFiles fns sg pp = do inputs <- readFiles fns - let igames = map readInput inputs - let cstruct = compstruct igames - return (gcstruct cstruct) +createComputationsFromFiles fileNames randomGen powerPhrase = do inputs <- readFiles fileNames + let igames = map readInput inputs + let cstruct = compstruct igames + return (gcstruct cstruct) where compstruct ig = concat (map genf ig) genf (i,g) = zipWith (\x (y,z) -> (x,y,z)) (replicate (length g) i) g - gcstruct cst = map (\(x,y,z) -> (x,y,j z))cst + gcstruct cst = map (\(x,y,z) -> (x,y,j z)) cst where - j z = strategies z sg (ppascommands pp) - ppascommands Nothing = Nothing - ppascommands (Just a) = Just (mapMaybe charToCommand a) + j game = strategies game randomGen (powerCommands powerPhrase) + powerCommands Nothing = Nothing + powerCommands (Just a) = Just (mapMaybe charToCommand a) readFiles :: [String] -> IO [BS.ByteString] readFiles [] = return [] @@ -112,28 +111,27 @@ readFiles (x:xs) = do f <- BS.readFile x instance NFData Command where rnf x = seq x () -iterategc :: [GameComputation] -> Maybe (Int,Int64) -> Maybe Int -> IO [(([Command], Int), Int)] -iterategc gcs tlimit mlimit = do rtl <- timeLimit tlimit - rml <- memLimit mlimit - if rtl || rml - then return best - else if (and $ map finishedGameComputation gcs) - then return best - else let mona = (applyNtimes gccompperstep itf gcs) - mona1 = map getBestGameComputation gcs - in mona1 `deepseq` (iterategc mona tlimit mlimit) - where - itf gcs1 = map advanceGameComputation gcs1 - applyNtimes 0 _ accum = accum - applyNtimes n f accum = applyNtimes (n - 1) f (f accum) - best = map getBestGameComputation gcs - -timeLimit :: Maybe (Int,Int64) -> IO Bool +iterateGame :: [GameComputation] -> Maybe (Double,Double) -> Maybe Int -> IO [FinishedGame] +iterateGame gameComputations timeLimitData memLimitData = do alive <- checkComputationAlive + if alive + then nextPass + else return bestGames + where + nextPass = (bestGames `deepseq` (iterateGame nextGameComputations timeLimitData memLimitData)) + nextGameComputations = (applyNtimes computationsPerStep advanceGameComputations gameComputations) + checkComputationAlive = do timeLimitFlag <- timeLimit timeLimitData + memLimitFlag <- memLimit memLimitData + let finishedComputation = (and $ map finishedGameComputation gameComputations) + return $ not (timeLimitFlag || memLimitFlag || finishedComputation) + advanceGameComputations computations = map advanceGameComputation computations + bestGames = map getBestGameComputation gameComputations + +timeLimit :: Maybe (Double, Double) -> IO Bool timeLimit Nothing = return False -timeLimit (Just (itime,limit)) = do atime <- secTime - let diff = (atime - (fromIntegral itime)) - return (((fromIntegral limit) * timeLimitRatio) < (fromIntegral diff)) - +timeLimit (Just (initialTime,stopTime)) = do actualTime <- secTime + let actualTimeD = fromIntegral actualTime + let timeDifference = (actualTimeD - initialTime) + return (stopTime <= timeDifference) memLimit :: Maybe Int -> IO Bool memLimit _ = return False @@ -147,9 +145,14 @@ writeLogFile False _ = return () writeLogFile _ els = writeFile logFileName scoredata where scoredata = foldl strlog "\n" els - strlog x (a,b,c,d) = sa ++ sb ++ sc ++ sd ++ x ++ "\n" + strlog x (a,b,c,d) = sa ++ sb ++ sc ++ sd ++ x ++ "\n\n" where sa = (show a) ++ " " sb = (show b) ++ " " sc = (show c) ++ " " sd = (show d) ++ " " + +applyNtimes :: Int -> (a -> a) -> a -> a +applyNtimes 0 _ accum = accum +applyNtimes n f accum = applyNtimes (n - 1) f (f accum) + diff --git a/src/StrategyManager.hs b/src/StrategyManager.hs index 915d779..cb8b3bb 100644 --- a/src/StrategyManager.hs +++ b/src/StrategyManager.hs @@ -5,8 +5,12 @@ module StrategyManager where import System.Random(StdGen) import Datatypes.Game(Game,Command) +type Score = Int +type StrategyIdx = Int +type FinishedGame = ([Command], Score, StrategyIdx) type GameComputation = [StrategyWrapper] + data StrategyWrapper = forall a . Strategy a => MkStrategyWrapper a | FinishedGame ([Command], Int) @@ -26,9 +30,9 @@ class Strategy a where advanceWrapper :: StrategyWrapper -> StrategyWrapper advanceWrapper (FinishedGame result) = (FinishedGame result) -advanceWrapper (MkStrategyWrapper st) = wrapResult $ advance st +advanceWrapper (MkStrategyWrapper strategy) = wrapResult $ advance strategy where - wrapResult (Left nst) = MkStrategyWrapper nst + wrapResult (Left nextStrategy) = MkStrategyWrapper nextStrategy wrapResult (Right result) = FinishedGame result finishedWrapper :: StrategyWrapper -> Bool @@ -44,12 +48,17 @@ finishedGameComputation :: GameComputation -> Bool finishedGameComputation gc = and $ map finishedWrapper gc -- Ritorna i comandi con i punti piu l indice della strategia -getBestGameComputation :: GameComputation -> (([Command], Int),Int) -getBestGameComputation gc = foldl bestgame (([], 0), 0) (map getbestWrapper gc) +getBestGameComputation :: GameComputation -> FinishedGame +getBestGameComputation gameComputation = bestGame where - bestgame (b,i) a = if (snd a) > (snd b) - then (a,i+1) - else (b,i) + resultsFromAlgorithms = (map getbestWrapper gameComputation) + algoIdxs = take (length resultsFromAlgorithms) [ i | i <- [0..]] + bestGames = zipWith (\(a,b) c -> (a,b,c)) resultsFromAlgorithms algoIdxs + bestGame = foldl findBest ([], 0, 0) bestGames + findBest best nextBest = if ((bestScore best) > (bestScore nextBest)) + then best + else nextBest + bestScore (_, score, _) = score advanceGameComputation :: GameComputation -> GameComputation advanceGameComputation gc = map advanceWrapper gc From e465ad3d0ca0e986b295d3d2ff28e34f300f6cde Mon Sep 17 00:00:00 2001 From: Slash Date: Mon, 10 Aug 2015 09:26:00 +0200 Subject: [PATCH 09/11] revenge of the submissions and the solutions --- ...0000000000000000000000000000000000000000000000626.strategy2b | 1 + ...0000000000000000000000000000000000000000000002831.strategy2b | 1 + ...0000000000000000000000000000000000000000000002011.strategy2b | 1 + ...0000000000000000000000000000000000000000000002373.strategy2b | 1 + ...0000000000000000000000000000000000000000000001357.strategy2b | 1 + ...0000000000000000000000000000000000000000000001812.strategy2b | 1 + ...0000000000000000000000000000000000000000000003313.strategy2b | 1 + ...0000000000000000000000000000000000000000000003108.strategy2b | 1 + ...0000000000000000000000000000000000000000000003064.strategy2b | 1 + ...0000000000000000000000000000000000000000000003224.strategy2b | 1 + ...0000000000000000000000000000000000000000000003310.strategy2b | 1 + ...0000000000000000000000000000000000000000000003126.strategy2b | 1 + ...0000000000000000000000000000000000000000000003326.strategy2b | 1 + ...0000000000000000000000000000000000000000000002723.strategy2b | 1 + ...0000000000000000000000000000000000000000000003084.strategy2b | 1 + ...0000000000000000000000000000000000000000000002935.strategy2b | 1 + ...0000000000000000000000000000000000000000000002061.strategy2b | 1 + ...0000000000000000000000000000000000000000000002353.strategy2b | 1 + ...0000000000000000000000000000000000000000000002552.strategy2b | 1 + ...0000000000000000000000000000000000000000000001650.strategy2b | 1 + ...0000000000000000000000000000000000000000000000941.strategy2b | 1 + ...0000000000000000000000000000000000000000000003759.strategy2b | 1 + ...0000000000000000000000000000000000000000000003510.strategy2b | 1 + ...0000000000000000000000000000000000000000000003613.strategy2b | 1 + ...0000000000000000000000000000000000000000000003507.strategy2b | 1 + ...0000000000000000000000000000000000000000000003475.strategy2b | 1 + ...0000000000000000000000000000000000000000000003727.strategy2b | 1 + ...0000000000000000000000000000000000000000000003562.strategy2b | 1 + ...0000000000000000000000000000000000000000000003684.strategy2b | 1 + ...0000000000000000000000000000000000000000000003557.strategy2b | 1 + ...0000000000000000000000000000000000000000000003606.strategy2b | 1 + ...0000000000000000000000000000000000000000000002757.strategy2b | 1 + ...0000000000000000000000000000000000000000000002847.strategy2b | 1 + ...0000000000000000000000000000000000000000000000974.strategy2b | 1 + ...0000000000000000000000000000000000000000000000993.strategy2b | 1 + ...0000000000000000000000000000000000000000000001311.strategy2b | 1 + ...0000000000000000000000000000000000000000000001958.strategy2b | 1 + ...0000000000000000000000000000000000000000000001313.strategy2b | 1 + ...0000000000000000000000000000000000000000000002780.strategy2b | 1 + ...0000000000000000000000000000000000000000000002370.strategy2b | 1 + ...0000000000000000000000000000000000000000000002198.strategy2b | 1 + ...0000000000000000000000000000000000000000000002744.strategy2b | 1 + ...0000000000000000000000000000000000000000000002400.strategy2b | 1 + ...0000000000000000000000000000000000000000000002464.strategy2b | 1 + ...0000000000000000000000000000000000000000000002774.strategy2b | 1 + ...0000000000000000000000000000000000000000000002688.strategy2b | 1 + ...0000000000000000000000000000000000000000000002770.strategy2b | 1 + ...0000000000000000000000000000000000000000000002038.strategy2b | 1 + ...0000000000000000000000000000000000000000000002804.strategy2b | 1 + ...0000000000000000000000000000000000000000000002900.strategy2b | 1 + ...0000000000000000000000000000000000000000000002386.strategy2b | 1 + ...0000000000000000000000000000000000000000000002720.strategy2b | 1 + ...0000000000000000000000000000000000000000000002098.strategy2b | 1 + ...0000000000000000000000000000000000000000000002048.strategy2b | 1 + ...0000000000000000000000000000000000000000000002388.strategy2b | 1 + ...0000000000000000000000000000000000000000000002408.strategy2b | 1 + ...0000000000000000000000000000000000000000000002770.strategy2b | 1 + ...0000000000000000000000000000000000000000000002340.strategy2b | 1 + ...0000000000000000000000000000000000000000000001742.strategy2b | 1 + ...0000000000000000000000000000000000000000000002062.strategy2b | 1 + ...0000000000000000000000000000000000000000000002784.strategy2b | 1 + ...0000000000000000000000000000000000000000000002742.strategy2b | 1 + ...0000000000000000000000000000000000000000000002698.strategy2b | 1 + ...0000000000000000000000000000000000000000000002060.strategy2b | 1 + ...0000000000000000000000000000000000000000000002764.strategy2b | 1 + ...0000000000000000000000000000000000000000000002140.strategy2b | 1 + ...0000000000000000000000000000000000000000000002462.strategy2b | 1 + ...0000000000000000000000000000000000000000000002892.strategy2b | 1 + ...0000000000000000000000000000000000000000000002560.strategy2b | 1 + ...0000000000000000000000000000000000000000000002078.strategy2b | 1 + ...0000000000000000000000000000000000000000000002040.strategy2b | 1 + ...0000000000000000000000000000000000000000000001712.strategy2b | 1 + ...0000000000000000000000000000000000000000000002808.strategy2b | 1 + ...0000000000000000000000000000000000000000000002144.strategy2b | 1 + ...0000000000000000000000000000000000000000000002352.strategy2b | 1 + ...0000000000000000000000000000000000000000000002362.strategy2b | 1 + ...0000000000000000000000000000000000000000000001716.strategy2b | 1 + ...0000000000000000000000000000000000000000000002404.strategy2b | 1 + ...0000000000000000000000000000000000000000000002040.strategy2b | 1 + ...0000000000000000000000000000000000000000000002404.strategy2b | 1 + ...0000000000000000000000000000000000000000000002728.strategy2b | 1 + ...0000000000000000000000000000000000000000000002394.strategy2b | 1 + ...0000000000000000000000000000000000000000000002398.strategy2b | 1 + ...0000000000000000000000000000000000000000000002714.strategy2b | 1 + ...0000000000000000000000000000000000000000000002690.strategy2b | 1 + ...0000000000000000000000000000000000000000000002382.strategy2b | 1 + ...0000000000000000000000000000000000000000000002754.strategy2b | 1 + ...0000000000000000000000000000000000000000000002552.strategy2b | 1 + ...0000000000000000000000000000000000000000000002355.strategy2b | 1 + ...0000000000000000000000000000000000000000000001695.strategy2b | 1 + ...0000000000000000000000000000000000000000000002073.strategy2b | 1 + ...0000000000000000000000000000000000000000000002004.strategy2b | 1 + ...0000000000000000000000000000000000000000000002326.strategy2b | 1 + ...0000000000000000000000000000000000000000000002358.strategy2b | 1 + ...0000000000000000000000000000000000000000000002346.strategy2b | 1 + ...0000000000000000000000000000000000000000000002022.strategy2b | 1 + ...0000000000000000000000000000000000000000000001942.strategy2b | 1 + ...0000000000000000000000000000000000000000000002454.strategy2b | 1 + ...0000000000000000000000000000000000000000000002973.strategy2b | 1 + ...0000000000000000000000000000000000000000000002142.strategy2b | 1 + ...0000000000000000000000000000000000000000000002466.strategy2b | 1 + ...0000000000000000000000000000000000000000000001980.strategy2b | 1 + ...0000000000000000000000000000000000000000000002529.strategy2b | 1 + ...0000000000000000000000000000000000000000000002457.strategy2b | 1 + ...0000000000000000000000000000000000000000000002351.strategy2b | 1 + ...0000000000000000000000000000000000000000000002369.strategy2b | 1 + ...0000000000000000000000000000000000000000000002039.strategy2b | 1 + ...0000000000000000000000000000000000000000000002736.strategy2b | 1 + ...0000000000000000000000000000000000000000000002416.strategy2b | 1 + ...0000000000000000000000000000000000000000000002398.strategy2b | 1 + ...0000000000000000000000000000000000000000000002129.strategy2b | 1 + ...0000000000000000000000000000000000000000000002946.strategy2b | 1 + ...0000000000000000000000000000000000000000000002443.strategy2b | 1 + ...0000000000000000000000000000000000000000000002168.strategy2b | 1 + ...0000000000000000000000000000000000000000000002056.strategy2b | 1 + ...0000000000000000000000000000000000000000000002317.strategy2b | 1 + ...0000000000000000000000000000000000000000000002844.strategy2b | 1 + ...0000000000000000000000000000000000000000000002785.strategy2b | 1 + ...0000000000000000000000000000000000000000000002474.strategy2b | 1 + ...0000000000000000000000000000000000000000000002453.strategy2b | 1 + ...0000000000000000000000000000000000000000000001977.strategy2b | 1 + ...0000000000000000000000000000000000000000000002407.strategy2b | 1 + ...0000000000000000000000000000000000000000000002306.strategy2b | 1 + ...0000000000000000000000000000000000000000000002770.strategy2b | 1 + ...0000000000000000000000000000000000000000000002824.strategy2b | 1 + ...0000000000000000000000000000000000000000000002841.strategy2b | 1 + ...0000000000000000000000000000000000000000000002487.strategy2b | 1 + ...0000000000000000000000000000000000000000000002430.strategy2b | 1 + ...0000000000000000000000000000000000000000000002386.strategy2b | 1 + ...0000000000000000000000000000000000000000000001954.strategy2b | 1 + ...0000000000000000000000000000000000000000000002042.strategy2b | 1 + ...0000000000000000000000000000000000000000000002578.strategy2b | 1 + ...0000000000000000000000000000000000000000000001964.strategy2b | 1 + ...0000000000000000000000000000000000000000000001669.strategy2b | 1 + ...0000000000000000000000000000000000000000000002408.strategy2b | 1 + ...0000000000000000000000000000000000000000000002516.strategy2b | 1 + ...0000000000000000000000000000000000000000000002243.strategy2b | 1 + ...0000000000000000000000000000000000000000000002435.strategy2b | 1 + ...0000000000000000000000000000000000000000000002483.strategy2b | 1 + ...0000000000000000000000000000000000000000000002383.strategy2b | 1 + ...0000000000000000000000000000000000000000000002810.strategy2b | 1 + ...0000000000000000000000000000000000000000000002380.strategy2b | 1 + ...0000000000000000000000000000000000000000000002393.strategy2b | 1 + ...0000000000000000000000000000000000000000000002486.strategy2b | 1 + ...0000000000000000000000000000000000000000000002444.strategy2b | 1 + ...0000000000000000000000000000000000000000000002444.strategy2b | 1 + ...0000000000000000000000000000000000000000000002384.strategy2b | 1 + ...0000000000000000000000000000000000000000000001719.strategy2b | 1 + ...0000000000000000000000000000000000000000000002292.strategy2b | 1 + ...0000000000000000000000000000000000000000000002278.strategy2b | 1 + ...0000000000000000000000000000000000000000000002068.strategy2b | 1 + ...0000000000000000000000000000000000000000000001735.strategy2b | 1 + ...0000000000000000000000000000000000000000000001057.strategy2b | 1 + ...0000000000000000000000000000000000000000000001728.strategy2b | 1 + ...0000000000000000000000000000000000000000000001041.strategy2b | 1 + ...0000000000000000000000000000000000000000000001007.strategy2b | 1 + ...0000000000000000000000000000000000000000000001007.strategy2b | 1 + ...0000000000000000000000000000000000000000000001159.strategy2b | 1 + ...0000000000000000000000000000000000000000000001377.strategy2b | 1 + ...0000000000000000000000000000000000000000000001359.strategy2b | 1 + ...0000000000000000000000000000000000000000000001782.strategy2b | 1 + ...0000000000000000000000000000000000000000000001820.strategy2b | 1 + ...0000000000000000000000000000000000000000000001301.strategy2b | 1 + ...0000000000000000000000000000000000000000000001092.strategy2b | 1 + ...0000000000000000000000000000000000000000000001281.strategy2b | 1 + ...0000000000000000000000000000000000000000000001830.strategy2b | 1 + ...0000000000000000000000000000000000000000000001101.strategy2b | 1 + submitted/10.json | 2 +- submitted/11.json | 2 +- submitted/12.json | 2 +- submitted/13.json | 2 +- submitted/14.json | 1 + submitted/15.json | 2 +- submitted/16.json | 2 +- submitted/17.json | 2 +- submitted/2.json | 2 +- submitted/20.json | 2 +- submitted/24.json | 2 +- submitted/3.json | 2 +- submitted/4.json | 2 +- submitted/5.json | 2 +- submitted/6.json | 2 +- submitted/7.json | 2 +- submitted/8.json | 2 +- submitted/9.json | 1 + 185 files changed, 185 insertions(+), 16 deletions(-) create mode 100644 solutions/10.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000626.strategy2b create mode 100644 solutions/11.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002831.strategy2b create mode 100644 solutions/11.12877.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002011.strategy2b create mode 100644 solutions/11.16526.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002373.strategy2b create mode 100644 solutions/11.19558.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001357.strategy2b create mode 100644 solutions/11.20528.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001812.strategy2b create mode 100644 solutions/12.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003313.strategy2b create mode 100644 solutions/12.1155.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003108.strategy2b create mode 100644 solutions/12.12700.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003064.strategy2b create mode 100644 solutions/12.18660.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003224.strategy2b create mode 100644 solutions/12.19102.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003310.strategy2b create mode 100644 solutions/12.24103.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003126.strategy2b create mode 100644 solutions/12.24762.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003326.strategy2b create mode 100644 solutions/12.24803.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002723.strategy2b create mode 100644 solutions/12.29992.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003084.strategy2b create mode 100644 solutions/12.5864.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002935.strategy2b create mode 100644 solutions/13.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002061.strategy2b create mode 100644 solutions/14.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002353.strategy2b create mode 100644 solutions/15.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002552.strategy2b create mode 100644 solutions/16.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001650.strategy2b create mode 100644 solutions/17.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000941.strategy2b create mode 100644 solutions/2.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003759.strategy2b create mode 100644 solutions/2.13639.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003510.strategy2b create mode 100644 solutions/2.13948.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003613.strategy2b create mode 100644 solutions/2.15385.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003507.strategy2b create mode 100644 solutions/2.16783.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003475.strategy2b create mode 100644 solutions/2.23027.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003727.strategy2b create mode 100644 solutions/2.23862.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003562.strategy2b create mode 100644 solutions/2.25221.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003684.strategy2b create mode 100644 solutions/2.29639.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003557.strategy2b create mode 100644 solutions/2.679.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003606.strategy2b create mode 100644 solutions/20.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002757.strategy2b create mode 100644 solutions/24.18.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002847.strategy2b create mode 100644 solutions/3.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000974.strategy2b create mode 100644 solutions/3.29060.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000993.strategy2b create mode 100644 solutions/3.31960.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001311.strategy2b create mode 100644 solutions/3.6094.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001958.strategy2b create mode 100644 solutions/3.6876.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001313.strategy2b create mode 100644 solutions/4.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002780.strategy2b create mode 100644 solutions/4.11006.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002370.strategy2b create mode 100644 solutions/4.12140.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002198.strategy2b create mode 100644 solutions/4.12272.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002744.strategy2b create mode 100644 solutions/4.12352.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002400.strategy2b create mode 100644 solutions/4.12976.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002464.strategy2b create mode 100644 solutions/4.13537.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002774.strategy2b create mode 100644 solutions/4.13661.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002688.strategy2b create mode 100644 solutions/4.13694.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002770.strategy2b create mode 100644 solutions/4.15766.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002038.strategy2b create mode 100644 solutions/4.16520.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002804.strategy2b create mode 100644 solutions/4.16868.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002900.strategy2b create mode 100644 solutions/4.17014.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002386.strategy2b create mode 100644 solutions/4.177.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002720.strategy2b create mode 100644 solutions/4.17818.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002098.strategy2b create mode 100644 solutions/4.18451.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002048.strategy2b create mode 100644 solutions/4.19530.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002388.strategy2b create mode 100644 solutions/4.19542.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002408.strategy2b create mode 100644 solutions/4.19957.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002770.strategy2b create mode 100644 solutions/4.20701.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002340.strategy2b create mode 100644 solutions/4.2148.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001742.strategy2b create mode 100644 solutions/4.21695.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002062.strategy2b create mode 100644 solutions/4.21791.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002784.strategy2b create mode 100644 solutions/4.22290.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002742.strategy2b create mode 100644 solutions/4.22345.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002698.strategy2b create mode 100644 solutions/4.22572.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002060.strategy2b create mode 100644 solutions/4.23008.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002764.strategy2b create mode 100644 solutions/4.23344.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002140.strategy2b create mode 100644 solutions/4.23414.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002462.strategy2b create mode 100644 solutions/4.2584.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002892.strategy2b create mode 100644 solutions/4.2586.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002560.strategy2b create mode 100644 solutions/4.26137.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002078.strategy2b create mode 100644 solutions/4.26153.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002040.strategy2b create mode 100644 solutions/4.26930.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001712.strategy2b create mode 100644 solutions/4.28635.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002808.strategy2b create mode 100644 solutions/4.28921.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002144.strategy2b create mode 100644 solutions/4.2895.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002352.strategy2b create mode 100644 solutions/4.29697.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002362.strategy2b create mode 100644 solutions/4.29707.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001716.strategy2b create mode 100644 solutions/4.29971.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002404.strategy2b create mode 100644 solutions/4.30014.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002040.strategy2b create mode 100644 solutions/4.31051.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002404.strategy2b create mode 100644 solutions/4.32001.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002728.strategy2b create mode 100644 solutions/4.6045.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002394.strategy2b create mode 100644 solutions/4.6532.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002398.strategy2b create mode 100644 solutions/4.7533.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002714.strategy2b create mode 100644 solutions/4.8269.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002690.strategy2b create mode 100644 solutions/4.8444.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002382.strategy2b create mode 100644 solutions/4.8466.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002754.strategy2b create mode 100644 solutions/4.8700.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002552.strategy2b create mode 100644 solutions/5.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002355.strategy2b create mode 100644 solutions/5.11460.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001695.strategy2b create mode 100644 solutions/5.14027.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002073.strategy2b create mode 100644 solutions/5.15215.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002004.strategy2b create mode 100644 solutions/5.15577.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002326.strategy2b create mode 100644 solutions/5.22837.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002358.strategy2b create mode 100644 solutions/5.24851.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002346.strategy2b create mode 100644 solutions/5.32620.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002022.strategy2b create mode 100644 solutions/5.32719.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001942.strategy2b create mode 100644 solutions/6.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002454.strategy2b create mode 100644 solutions/6.10919.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002973.strategy2b create mode 100644 solutions/6.11993.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002142.strategy2b create mode 100644 solutions/6.13120.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002466.strategy2b create mode 100644 solutions/6.13185.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001980.strategy2b create mode 100644 solutions/6.13859.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002529.strategy2b create mode 100644 solutions/6.14118.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002457.strategy2b create mode 100644 solutions/6.1519.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002351.strategy2b create mode 100644 solutions/6.15379.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002369.strategy2b create mode 100644 solutions/6.15671.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002039.strategy2b create mode 100644 solutions/6.16393.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002736.strategy2b create mode 100644 solutions/6.16650.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002416.strategy2b create mode 100644 solutions/6.16903.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002398.strategy2b create mode 100644 solutions/6.17013.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002129.strategy2b create mode 100644 solutions/6.17114.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002946.strategy2b create mode 100644 solutions/6.18093.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002443.strategy2b create mode 100644 solutions/6.18588.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002168.strategy2b create mode 100644 solutions/6.19086.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002056.strategy2b create mode 100644 solutions/6.21458.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002317.strategy2b create mode 100644 solutions/6.21728.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002844.strategy2b create mode 100644 solutions/6.22079.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002785.strategy2b create mode 100644 solutions/6.23220.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002474.strategy2b create mode 100644 solutions/6.23256.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002453.strategy2b create mode 100644 solutions/6.24334.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001977.strategy2b create mode 100644 solutions/6.24513.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002407.strategy2b create mode 100644 solutions/6.24524.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002306.strategy2b create mode 100644 solutions/6.24732.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002770.strategy2b create mode 100644 solutions/6.25267.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002824.strategy2b create mode 100644 solutions/6.25460.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002841.strategy2b create mode 100644 solutions/6.25499.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002487.strategy2b create mode 100644 solutions/6.25536.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002430.strategy2b create mode 100644 solutions/6.26670.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002386.strategy2b create mode 100644 solutions/6.26708.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001954.strategy2b create mode 100644 solutions/6.26906.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002042.strategy2b create mode 100644 solutions/6.28599.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002578.strategy2b create mode 100644 solutions/6.2860.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001964.strategy2b create mode 100644 solutions/6.29169.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001669.strategy2b create mode 100644 solutions/6.31026.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002408.strategy2b create mode 100644 solutions/6.3703.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002516.strategy2b create mode 100644 solutions/6.5343.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002243.strategy2b create mode 100644 solutions/6.629.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002435.strategy2b create mode 100644 solutions/6.6839.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002483.strategy2b create mode 100644 solutions/6.7082.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002383.strategy2b create mode 100644 solutions/6.7610.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002810.strategy2b create mode 100644 solutions/6.8123.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002380.strategy2b create mode 100644 solutions/6.8466.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002393.strategy2b create mode 100644 solutions/6.8780.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002486.strategy2b create mode 100644 solutions/6.8856.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002444.strategy2b create mode 100644 solutions/6.9536.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002444.strategy2b create mode 100644 solutions/6.9816.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002384.strategy2b create mode 100644 solutions/7.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001719.strategy2b create mode 100644 solutions/7.16651.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002292.strategy2b create mode 100644 solutions/7.18705.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002278.strategy2b create mode 100644 solutions/7.22828.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002068.strategy2b create mode 100644 solutions/7.27669.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001735.strategy2b create mode 100644 solutions/8.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001057.strategy2b create mode 100644 solutions/8.10596.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001728.strategy2b create mode 100644 solutions/8.14104.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001041.strategy2b create mode 100644 solutions/8.19012.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001007.strategy2b create mode 100644 solutions/8.20240.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001007.strategy2b create mode 100644 solutions/8.2629.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001159.strategy2b create mode 100644 solutions/8.28581.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001377.strategy2b create mode 100644 solutions/8.4491.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001359.strategy2b create mode 100644 solutions/8.5696.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001782.strategy2b create mode 100644 solutions/8.8000.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001820.strategy2b create mode 100644 solutions/9.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001301.strategy2b create mode 100644 solutions/9.10998.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001092.strategy2b create mode 100644 solutions/9.23855.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001281.strategy2b create mode 100644 solutions/9.26637.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001830.strategy2b create mode 100644 solutions/9.4150.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001101.strategy2b create mode 100644 submitted/14.json create mode 100644 submitted/9.json diff --git a/solutions/10.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000626.strategy2b b/solutions/10.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000626.strategy2b new file mode 100644 index 0000000..5657510 --- /dev/null +++ b/solutions/10.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000626.strategy2b @@ -0,0 +1 @@ +{"seed": 0, "tag": "strategy2b", "solution": "dei!kd r'lyeh", "problemId": 10} \ No newline at end of file diff --git a/solutions/11.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002831.strategy2b b/solutions/11.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002831.strategy2b new file mode 100644 index 0000000..8504535 --- /dev/null +++ b/solutions/11.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002831.strategy2b @@ -0,0 +1 @@ +{"seed": 0, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!yuggothei!john bigbootejohn bigbooteyogsothoth r'lyehjohn bigboote r'lyehplkakkei!akei!kkei! r'lyehppppdei!kei!", "problemId": 11} \ No newline at end of file diff --git a/solutions/11.12877.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002011.strategy2b b/solutions/11.12877.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002011.strategy2b new file mode 100644 index 0000000..3a2da78 --- /dev/null +++ b/solutions/11.12877.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002011.strategy2b @@ -0,0 +1 @@ +{"seed": 12877, "tag": "strategy2b", "solution": "john bigbootenecronomiconyogsothothia! ia!necronomiconei!ia! ia!ia! ia!aaei!alei! r'lyehpkpddei!kei!l", "problemId": 11} \ No newline at end of file diff --git a/solutions/11.16526.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002373.strategy2b b/solutions/11.16526.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002373.strategy2b new file mode 100644 index 0000000..e145810 --- /dev/null +++ b/solutions/11.16526.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002373.strategy2b @@ -0,0 +1 @@ +{"seed": 16526, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconei!kpia! ia!pabllb r'lyehei!alkei!dei!pdppkppppdei!l", "problemId": 11} \ No newline at end of file diff --git a/solutions/11.19558.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001357.strategy2b b/solutions/11.19558.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001357.strategy2b new file mode 100644 index 0000000..1ecf3e6 --- /dev/null +++ b/solutions/11.19558.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001357.strategy2b @@ -0,0 +1 @@ +{"seed": 19558, "tag": "strategy2b", "solution": "john bigbooteia! ia!john bigboote r'lyehei!aei!aei!lei!ei!aei!aaaadaddlabbkbkbb r'lyeh", "problemId": 11} \ No newline at end of file diff --git a/solutions/11.20528.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001812.strategy2b b/solutions/11.20528.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001812.strategy2b new file mode 100644 index 0000000..0999025 --- /dev/null +++ b/solutions/11.20528.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001812.strategy2b @@ -0,0 +1 @@ +{"seed": 20528, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteia! ia!john bigbooteei!ia! ia!ia! ia!aei!abbbei!aei!ia! ia!ei!aaaei!kpddei!adaabkei!", "problemId": 11} \ No newline at end of file diff --git a/solutions/12.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003313.strategy2b b/solutions/12.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003313.strategy2b new file mode 100644 index 0000000..58593d4 --- /dev/null +++ b/solutions/12.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003313.strategy2b @@ -0,0 +1 @@ +{"seed": 0, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootejohn bigbootejohn bigbootejohn bigbootejohn bigbootejohn bigbootejohn bigbootenecronomiconyuggothjohn bigbootejohn bigbootenecronomiconia! ia!ia! ia! r'lyehia! ia!adbbkbbbb r'lyehpl", "problemId": 12} \ No newline at end of file diff --git a/solutions/12.1155.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003108.strategy2b b/solutions/12.1155.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003108.strategy2b new file mode 100644 index 0000000..aebb906 --- /dev/null +++ b/solutions/12.1155.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003108.strategy2b @@ -0,0 +1 @@ +{"seed": 1155, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothyuggothia! ia!john bigbooteei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootejohn bigbootejohn bigbooteia! ia!necronomiconnecronomiconnecronomiconjohn bigbooteei!aaapia! ia!aei! r'lyehia! ia!l r'lyehpkei!l", "problemId": 12} \ No newline at end of file diff --git a/solutions/12.12700.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003064.strategy2b b/solutions/12.12700.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003064.strategy2b new file mode 100644 index 0000000..8f0ea33 --- /dev/null +++ b/solutions/12.12700.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003064.strategy2b @@ -0,0 +1 @@ +{"seed": 12700, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ia! ia!john bigbooteia! ia!aei! r'lyehpkabkyogsothothei!aei!kb r'lyehpl", "problemId": 12} \ No newline at end of file diff --git a/solutions/12.18660.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003224.strategy2b b/solutions/12.18660.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003224.strategy2b new file mode 100644 index 0000000..7a7283a --- /dev/null +++ b/solutions/12.18660.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003224.strategy2b @@ -0,0 +1 @@ +{"seed": 18660, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothyuggothia! ia!john bigbooteei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootejohn bigbooteyogsothothjohn bigbootejohn bigbootenecronomiconjohn bigbooteei!ei!ia! ia!aei!ayuggoth r'lyehpd r'lyehei!aei!dppkei!pdei!l", "problemId": 12} \ No newline at end of file diff --git a/solutions/12.19102.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003310.strategy2b b/solutions/12.19102.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003310.strategy2b new file mode 100644 index 0000000..b6139f9 --- /dev/null +++ b/solutions/12.19102.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003310.strategy2b @@ -0,0 +1 @@ +{"seed": 19102, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothyuggothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteei!john bigbootejohn bigbootejohn bigbootejohn bigbootejohn bigbootejohn bigbootenecronomiconyuggothyuggoth r'lyehpkblalaaei!akaaei!akaei!pppppkbbbbbbb r'lyeh", "problemId": 12} \ No newline at end of file diff --git a/solutions/12.24103.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003126.strategy2b b/solutions/12.24103.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003126.strategy2b new file mode 100644 index 0000000..ec43ec9 --- /dev/null +++ b/solutions/12.24103.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003126.strategy2b @@ -0,0 +1 @@ +{"seed": 24103, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconia! ia!ia! ia!john bigbooteyuggothnecronomiconia! ia!aaa r'lyeh r'lyehei!aaei!kb r'lyehpl", "problemId": 12} \ No newline at end of file diff --git a/solutions/12.24762.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003326.strategy2b b/solutions/12.24762.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003326.strategy2b new file mode 100644 index 0000000..7cf865f --- /dev/null +++ b/solutions/12.24762.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003326.strategy2b @@ -0,0 +1 @@ +{"seed": 24762, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!john bigbooteyogsothothjohn bigbooteia! ia!ia! ia!aei!a r'lyehia! ia!alei!l r'lyeh", "problemId": 12} \ No newline at end of file diff --git a/solutions/12.24803.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002723.strategy2b b/solutions/12.24803.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002723.strategy2b new file mode 100644 index 0000000..b857730 --- /dev/null +++ b/solutions/12.24803.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002723.strategy2b @@ -0,0 +1 @@ +{"seed": 24803, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothyuggothia! ia!pei!pia! ia!aei! r'lyehia! ia!aei!lei!l r'lyeh", "problemId": 12} \ No newline at end of file diff --git a/solutions/12.29992.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003084.strategy2b b/solutions/12.29992.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003084.strategy2b new file mode 100644 index 0000000..9708876 --- /dev/null +++ b/solutions/12.29992.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003084.strategy2b @@ -0,0 +1 @@ +{"seed": 29992, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!john bigbooteyuggothei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootejohn bigbooteia! ia!knecronomiconaaei!lei!aei! r'lyehpaei!aei!pdpkpdppkei!l", "problemId": 12} \ No newline at end of file diff --git a/solutions/12.5864.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002935.strategy2b b/solutions/12.5864.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002935.strategy2b new file mode 100644 index 0000000..159d38f --- /dev/null +++ b/solutions/12.5864.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002935.strategy2b @@ -0,0 +1 @@ +{"seed": 5864, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothyuggothia! ia!john bigbooteei!john bigbootejohn bigbootejohn bigbootejohn bigbooteia! ia! r'lyehia! ia!akpakpkkei!ayogsothothkia! ia!aei!aei! r'lyehpapp r'lyeh", "problemId": 12} \ No newline at end of file diff --git a/solutions/13.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002061.strategy2b b/solutions/13.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002061.strategy2b new file mode 100644 index 0000000..4e4e327 --- /dev/null +++ b/solutions/13.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002061.strategy2b @@ -0,0 +1 @@ +{"seed": 0, "tag": "strategy2b", "solution": "necronomiconia! ia!john bigbooteyogsothoth r'lyehpakia! ia!ei!kkakkkpkkkkkpddddppkei!kkkbkbddddldbdddbkbkpkkbddei!kei!", "problemId": 13} \ No newline at end of file diff --git a/solutions/14.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002353.strategy2b b/solutions/14.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002353.strategy2b new file mode 100644 index 0000000..e34227a --- /dev/null +++ b/solutions/14.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002353.strategy2b @@ -0,0 +1 @@ +{"seed": 0, "tag": "strategy2b", "solution": "ia! ia!ia! ia!john bigbootenecronomiconyuggothalappkaei!pklbbbdei!dldbdlbklbdbllblkbnecronomiconyogsothoth r'lyehjohn bigbooteia! ia!john bigbooteapl", "problemId": 14} \ No newline at end of file diff --git a/solutions/15.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002552.strategy2b b/solutions/15.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002552.strategy2b new file mode 100644 index 0000000..c36036d --- /dev/null +++ b/solutions/15.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002552.strategy2b @@ -0,0 +1 @@ +{"seed": 0, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.bbei!ppia! ia!pppia! ia!ppabppppalalalia! ia!pppalalalaadppppalalalakppppalalkppppakppppkpkl", "problemId": 15} \ No newline at end of file diff --git a/solutions/16.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001650.strategy2b b/solutions/16.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001650.strategy2b new file mode 100644 index 0000000..c35846b --- /dev/null +++ b/solutions/16.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001650.strategy2b @@ -0,0 +1 @@ +{"seed": 0, "tag": "strategy2b", "solution": "ia! ia!john bigbootenecronomiconia! ia!lei!bbei!bei!ppia! ia!ppppaayuggoth", "problemId": 16} \ No newline at end of file diff --git a/solutions/17.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000941.strategy2b b/solutions/17.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000941.strategy2b new file mode 100644 index 0000000..08721ac --- /dev/null +++ b/solutions/17.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000941.strategy2b @@ -0,0 +1 @@ +{"seed": 0, "tag": "strategy2b", "solution": "ia! ia!ia! ia!ia! ia!ei!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!aia! ia!ei!ei!pia! ia!aei!pia! ia!lppia! ia!ppia! ia!pabpppia! ia!ppabppppia! ia!ppppia! ia!pppabpppppia! ia!ppppabppppppaaei!ppppppaaei!pppppaabppppppabpppppppppppppppppppppppppppppppppppl", "problemId": 17} \ No newline at end of file diff --git a/solutions/2.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003759.strategy2b b/solutions/2.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003759.strategy2b new file mode 100644 index 0000000..4a13a4d --- /dev/null +++ b/solutions/2.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003759.strategy2b @@ -0,0 +1 @@ +{"seed": 0, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomicon r'lyehpkakpakaaalyuggothei!kei!", "problemId": 2} \ No newline at end of file diff --git a/solutions/2.13639.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003510.strategy2b b/solutions/2.13639.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003510.strategy2b new file mode 100644 index 0000000..5e77450 --- /dev/null +++ b/solutions/2.13639.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003510.strategy2b @@ -0,0 +1 @@ +{"seed": 13639, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootejohn bigbootenecronomiconnecronomiconph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconia! ia!dei!pdlkabei!ldbldlbkei!kdbbldddbkkkbddbkei!dddei!lei!", "problemId": 2} \ No newline at end of file diff --git a/solutions/2.13948.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003613.strategy2b b/solutions/2.13948.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003613.strategy2b new file mode 100644 index 0000000..3643bff --- /dev/null +++ b/solutions/2.13948.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003613.strategy2b @@ -0,0 +1 @@ +{"seed": 13948, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!necronomiconnecronomiconnecronomiconnecronomiconia! ia!ayuggoth r'lyehpkkkpkklblblddbkkei!kei!l", "problemId": 2} \ No newline at end of file diff --git a/solutions/2.15385.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003507.strategy2b b/solutions/2.15385.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003507.strategy2b new file mode 100644 index 0000000..d94aff8 --- /dev/null +++ b/solutions/2.15385.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003507.strategy2b @@ -0,0 +1 @@ +{"seed": 15385, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootejohn bigbootejohn bigbootejohn bigbootenecronomiconph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn. r'lyehei!ia! ia! r'lyehyuggothia! ia! r'lyehpdia! ia!ia! ia!ia! ia!aadpkia! ia!padddpapakpkei!dddbkkei!", "problemId": 2} \ No newline at end of file diff --git a/solutions/2.16783.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003475.strategy2b b/solutions/2.16783.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003475.strategy2b new file mode 100644 index 0000000..a701287 --- /dev/null +++ b/solutions/2.16783.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003475.strategy2b @@ -0,0 +1 @@ +{"seed": 16783, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!john bigbootenecronomiconnecronomiconyogsothothia! ia!aadaaaa r'lyehyuggothkpkkei!kei!kei!", "problemId": 2} \ No newline at end of file diff --git a/solutions/2.23027.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003727.strategy2b b/solutions/2.23027.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003727.strategy2b new file mode 100644 index 0000000..496cd46 --- /dev/null +++ b/solutions/2.23027.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003727.strategy2b @@ -0,0 +1 @@ +{"seed": 23027, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!john bigbooteyuggothei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootejohn bigbootenecronomiconia! ia!ia! ia!dei!ppadpkaapalkjohn bigbootedaei!kkakkei!kpdpdpaei!", "problemId": 2} \ No newline at end of file diff --git a/solutions/2.23862.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003562.strategy2b b/solutions/2.23862.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003562.strategy2b new file mode 100644 index 0000000..fe66b30 --- /dev/null +++ b/solutions/2.23862.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003562.strategy2b @@ -0,0 +1 @@ +{"seed": 23862, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!necronomicon r'lyehia! ia! r'lyehpia! ia!aakakdpkkkkei!ppaapaakei!lalei!labdei!l", "problemId": 2} \ No newline at end of file diff --git a/solutions/2.25221.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003684.strategy2b b/solutions/2.25221.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003684.strategy2b new file mode 100644 index 0000000..0036784 --- /dev/null +++ b/solutions/2.25221.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003684.strategy2b @@ -0,0 +1 @@ +{"seed": 25221, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!necronomiconyogsothoth r'lyehyuggothei!akia! ia!alei!labdbdblbkkkkkei!lei!dei!l", "problemId": 2} \ No newline at end of file diff --git a/solutions/2.29639.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003557.strategy2b b/solutions/2.29639.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003557.strategy2b new file mode 100644 index 0000000..580b27c --- /dev/null +++ b/solutions/2.29639.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003557.strategy2b @@ -0,0 +1 @@ +{"seed": 29639, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.yuggothei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconia! ia! r'lyehpia! ia!ayogsothothkkkkei!ia! ia!ayuggothkyuggothkkei!p", "problemId": 2} \ No newline at end of file diff --git a/solutions/2.679.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003606.strategy2b b/solutions/2.679.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003606.strategy2b new file mode 100644 index 0000000..8273526 --- /dev/null +++ b/solutions/2.679.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000003606.strategy2b @@ -0,0 +1 @@ +{"seed": 679, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconnecronomiconjohn bigbootejohn bigbootejohn bigbooteia! ia!john bigbooteapia! ia! r'lyehia! ia!akei!", "problemId": 2} \ No newline at end of file diff --git a/solutions/20.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002757.strategy2b b/solutions/20.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002757.strategy2b new file mode 100644 index 0000000..34e8ea3 --- /dev/null +++ b/solutions/20.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002757.strategy2b @@ -0,0 +1 @@ +{"seed": 0, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothyuggothia! ia!john bigbooteei!john bigbooteyuggothei!lbddei!aei!abbbkbbbk r'lyehpl", "problemId": 20} \ No newline at end of file diff --git a/solutions/24.18.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002847.strategy2b b/solutions/24.18.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002847.strategy2b new file mode 100644 index 0000000..a4ad340 --- /dev/null +++ b/solutions/24.18.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002847.strategy2b @@ -0,0 +1 @@ +{"seed": 18, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ia! ia!ia! ia! r'lyehei! r'lyeh r'lyehppaap r'lyehbbdei!kppkkei!kkaabyuggothjohn bigbootenecronomiconyogsothoth r'lyehnecronomiconei!aei!l", "problemId": 24} \ No newline at end of file diff --git a/solutions/3.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000974.strategy2b b/solutions/3.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000974.strategy2b new file mode 100644 index 0000000..527312e --- /dev/null +++ b/solutions/3.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000974.strategy2b @@ -0,0 +1 @@ +{"seed": 0, "tag": "strategy2b", "solution": "john bigbooteei!ia! ia!aakkakaaakkkkkppppddbkbddddei!dpkkei!", "problemId": 3} \ No newline at end of file diff --git a/solutions/3.29060.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000993.strategy2b b/solutions/3.29060.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000993.strategy2b new file mode 100644 index 0000000..6895560 --- /dev/null +++ b/solutions/3.29060.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000993.strategy2b @@ -0,0 +1 @@ +{"seed": 29060, "tag": "strategy2b", "solution": "necronomicon r'lyehpabbbbdblllkkl r'lyehpkbkei!kei!", "problemId": 3} \ No newline at end of file diff --git a/solutions/3.31960.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001311.strategy2b b/solutions/3.31960.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001311.strategy2b new file mode 100644 index 0000000..4ffc57a --- /dev/null +++ b/solutions/3.31960.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001311.strategy2b @@ -0,0 +1 @@ +{"seed": 31960, "tag": "strategy2b", "solution": "necronomiconia! ia! r'lyehpabbbbdblllkkl r'lyehpkbkei!kei!", "problemId": 3} \ No newline at end of file diff --git a/solutions/3.6094.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001958.strategy2b b/solutions/3.6094.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001958.strategy2b new file mode 100644 index 0000000..3e5b6f7 --- /dev/null +++ b/solutions/3.6094.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001958.strategy2b @@ -0,0 +1 @@ +{"seed": 6094, "tag": "strategy2b", "solution": "john bigbootelei!ia! ia!ei!kpkkpabdppppkpia! ia!pppppda r'lyehpdpkppppaabdpkpdpkpdpkpapaaklkkpdpkpdpkaalei!lyuggothyogsothothl", "problemId": 3} \ No newline at end of file diff --git a/solutions/3.6876.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001313.strategy2b b/solutions/3.6876.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001313.strategy2b new file mode 100644 index 0000000..4ef0271 --- /dev/null +++ b/solutions/3.6876.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001313.strategy2b @@ -0,0 +1 @@ +{"seed": 6876, "tag": "strategy2b", "solution": "john bigbooteei!a r'lyehplkpaklkkpdpkia! ia!adbkbdlldlia! ia! r'lyeh", "problemId": 3} \ No newline at end of file diff --git a/solutions/4.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002780.strategy2b b/solutions/4.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002780.strategy2b new file mode 100644 index 0000000..7245886 --- /dev/null +++ b/solutions/4.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002780.strategy2b @@ -0,0 +1 @@ +{"seed": 0, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteia! ia!necronomiconyogsothothyuggothei!john bigbootenecronomiconei!pdia! ia!paa r'lyehppakei!kei!lei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.11006.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002370.strategy2b b/solutions/4.11006.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002370.strategy2b new file mode 100644 index 0000000..24540f1 --- /dev/null +++ b/solutions/4.11006.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002370.strategy2b @@ -0,0 +1 @@ +{"seed": 11006, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothia! ia!necronomiconei!ab r'lyehpaallallei!ldei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.12140.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002198.strategy2b b/solutions/4.12140.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002198.strategy2b new file mode 100644 index 0000000..572d558 --- /dev/null +++ b/solutions/4.12140.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002198.strategy2b @@ -0,0 +1 @@ +{"seed": 12140, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconbpia! ia!aalbdallkkkei!lei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.12272.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002744.strategy2b b/solutions/4.12272.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002744.strategy2b new file mode 100644 index 0000000..b8a2ca8 --- /dev/null +++ b/solutions/4.12272.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002744.strategy2b @@ -0,0 +1 @@ +{"seed": 12272, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia! r'lyehyuggothei!ia! ia! r'lyehpbdbllei!ppkbbbbkbdei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.12352.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002400.strategy2b b/solutions/4.12352.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002400.strategy2b new file mode 100644 index 0000000..5f439cc --- /dev/null +++ b/solutions/4.12352.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002400.strategy2b @@ -0,0 +1 @@ +{"seed": 12352, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothyuggothia! ia!ei! r'lyehei!apkia! ia!akaadbbei!paddei!lei!l", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.12976.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002464.strategy2b b/solutions/4.12976.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002464.strategy2b new file mode 100644 index 0000000..a25197b --- /dev/null +++ b/solutions/4.12976.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002464.strategy2b @@ -0,0 +1 @@ +{"seed": 12976, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!ia! ia!lei!aadbbyogsothoth", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.13537.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002774.strategy2b b/solutions/4.13537.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002774.strategy2b new file mode 100644 index 0000000..c8254a7 --- /dev/null +++ b/solutions/4.13537.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002774.strategy2b @@ -0,0 +1 @@ +{"seed": 13537, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothyuggothnecronomiconia! ia!necronomiconei!necronomiconpia! ia!kapa r'lyehyuggothkbblblkkei!lei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.13661.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002688.strategy2b b/solutions/4.13661.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002688.strategy2b new file mode 100644 index 0000000..6ace6d0 --- /dev/null +++ b/solutions/4.13661.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002688.strategy2b @@ -0,0 +1 @@ +{"seed": 13661, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothyuggothia! ia!ia! ia!klbbllei!dbei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.13694.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002770.strategy2b b/solutions/4.13694.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002770.strategy2b new file mode 100644 index 0000000..a6844c2 --- /dev/null +++ b/solutions/4.13694.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002770.strategy2b @@ -0,0 +1 @@ +{"seed": 13694, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteia! ia!necronomiconyogsothothyuggothei!john bigbooteyogsothothia! ia!ia! ia!lpkei!kkakpppdpkpaei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.15766.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002038.strategy2b b/solutions/4.15766.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002038.strategy2b new file mode 100644 index 0000000..97d1ea6 --- /dev/null +++ b/solutions/4.15766.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002038.strategy2b @@ -0,0 +1 @@ +{"seed": 15766, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothyuggothei!dei!ppkblyuggoth", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.16520.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002804.strategy2b b/solutions/4.16520.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002804.strategy2b new file mode 100644 index 0000000..0ba90c8 --- /dev/null +++ b/solutions/4.16520.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002804.strategy2b @@ -0,0 +1 @@ +{"seed": 16520, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothyuggothia! ia!ei!necronomiconpadbbbei!appaei!pkadabbbbdei!kkkkkbddddbdei!a", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.16868.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002900.strategy2b b/solutions/4.16868.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002900.strategy2b new file mode 100644 index 0000000..61288bc --- /dev/null +++ b/solutions/4.16868.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002900.strategy2b @@ -0,0 +1 @@ +{"seed": 16868, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!john bigbooteei!john bigbooteyuggothyogsothothnecronomiconei!adabkkkpppdbbbkei!bbkkl", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.17014.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002386.strategy2b b/solutions/4.17014.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002386.strategy2b new file mode 100644 index 0000000..ccb112f --- /dev/null +++ b/solutions/4.17014.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002386.strategy2b @@ -0,0 +1 @@ +{"seed": 17014, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!ia! ia!ei!kpablbbddadbdbkblbdlalaei!lei!ayuggothbkkei!kbei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.177.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002720.strategy2b b/solutions/4.177.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002720.strategy2b new file mode 100644 index 0000000..c44bce6 --- /dev/null +++ b/solutions/4.177.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002720.strategy2b @@ -0,0 +1 @@ +{"seed": 177, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia! r'lyehei!ia! ia!kablbyuggothkabbkbei!ppkdbkkei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.17818.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002098.strategy2b b/solutions/4.17818.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002098.strategy2b new file mode 100644 index 0000000..fcaac9d --- /dev/null +++ b/solutions/4.17818.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002098.strategy2b @@ -0,0 +1 @@ +{"seed": 17818, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!john bigbootedbei!apppkalalei!lei!lei!lei!dpkpddlkppaei!l", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.18451.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002048.strategy2b b/solutions/4.18451.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002048.strategy2b new file mode 100644 index 0000000..78d61f3 --- /dev/null +++ b/solutions/4.18451.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002048.strategy2b @@ -0,0 +1 @@ +{"seed": 18451, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!dlbei!bblei!kpkpddei!kei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.19530.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002388.strategy2b b/solutions/4.19530.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002388.strategy2b new file mode 100644 index 0000000..079b7b9 --- /dev/null +++ b/solutions/4.19530.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002388.strategy2b @@ -0,0 +1 @@ +{"seed": 19530, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconei!ia! ia!akappia! ia!bbbei!ppdei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.19542.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002408.strategy2b b/solutions/4.19542.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002408.strategy2b new file mode 100644 index 0000000..37e696a --- /dev/null +++ b/solutions/4.19542.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002408.strategy2b @@ -0,0 +1 @@ +{"seed": 19542, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!necronomiconei!kia! ia!kkapllbei!bbei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.19957.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002770.strategy2b b/solutions/4.19957.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002770.strategy2b new file mode 100644 index 0000000..04e970e --- /dev/null +++ b/solutions/4.19957.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002770.strategy2b @@ -0,0 +1 @@ +{"seed": 19957, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteia! ia!necronomiconyogsothothei!ia! ia!john bigbooteyuggothia! ia!ia! ia!lppkei!kkei!ppkbbei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.20701.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002340.strategy2b b/solutions/4.20701.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002340.strategy2b new file mode 100644 index 0000000..4adc063 --- /dev/null +++ b/solutions/4.20701.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002340.strategy2b @@ -0,0 +1 @@ +{"seed": 20701, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconbblei!kia! ia!pkaalayuggoth", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.2148.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001742.strategy2b b/solutions/4.2148.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001742.strategy2b new file mode 100644 index 0000000..b000c04 --- /dev/null +++ b/solutions/4.2148.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001742.strategy2b @@ -0,0 +1 @@ +{"seed": 2148, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconbei!aanecronomiconakpk r'lyeh", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.21695.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002062.strategy2b b/solutions/4.21695.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002062.strategy2b new file mode 100644 index 0000000..02f1530 --- /dev/null +++ b/solutions/4.21695.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002062.strategy2b @@ -0,0 +1 @@ +{"seed": 21695, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconei!akia! ia!kapa r'lyehei!akkkei!kppddddei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.21791.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002784.strategy2b b/solutions/4.21791.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002784.strategy2b new file mode 100644 index 0000000..56b8b29 --- /dev/null +++ b/solutions/4.21791.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002784.strategy2b @@ -0,0 +1 @@ +{"seed": 21791, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!john bigbooteei!john bigbooteyuggothia! ia!kkia! ia!aabbdlbkei!blbei!dpkpakldpppkakl", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.22290.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002742.strategy2b b/solutions/4.22290.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002742.strategy2b new file mode 100644 index 0000000..ed50715 --- /dev/null +++ b/solutions/4.22290.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002742.strategy2b @@ -0,0 +1 @@ +{"seed": 22290, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteia! ia!necronomiconyuggothyogsothothei!necronomiconei!kei!akbkei!kpia! ia!akapkkbkpkbdpkpkkkkpkei!l", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.22345.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002698.strategy2b b/solutions/4.22345.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002698.strategy2b new file mode 100644 index 0000000..10c7eb0 --- /dev/null +++ b/solutions/4.22345.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002698.strategy2b @@ -0,0 +1 @@ +{"seed": 22345, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!john bigbooteyuggothei!aei!akkkei!l", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.22572.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002060.strategy2b b/solutions/4.22572.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002060.strategy2b new file mode 100644 index 0000000..d6445f9 --- /dev/null +++ b/solutions/4.22572.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002060.strategy2b @@ -0,0 +1 @@ +{"seed": 22572, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!ia! ia!ia! ia!apdbdbei!dbddddei!l", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.23008.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002764.strategy2b b/solutions/4.23008.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002764.strategy2b new file mode 100644 index 0000000..04899e4 --- /dev/null +++ b/solutions/4.23008.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002764.strategy2b @@ -0,0 +1 @@ +{"seed": 23008, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!john bigbooteyuggothei!john bigbooteyuggothei!bbei!aadppkpkkei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.23344.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002140.strategy2b b/solutions/4.23344.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002140.strategy2b new file mode 100644 index 0000000..42931fc --- /dev/null +++ b/solutions/4.23344.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002140.strategy2b @@ -0,0 +1 @@ +{"seed": 23344, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!john bigbooteei!ia! ia! r'lyehei! r'lyehpkbbei!lbkbddei!lkei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.23414.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002462.strategy2b b/solutions/4.23414.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002462.strategy2b new file mode 100644 index 0000000..b0fc618 --- /dev/null +++ b/solutions/4.23414.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002462.strategy2b @@ -0,0 +1 @@ +{"seed": 23414, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothia! ia!necronomiconei!john bigbooteia! ia!ia! ia!pkadlbldyogsothothdlblei!dblkbdei!bbbblkbei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.2584.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002892.strategy2b b/solutions/4.2584.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002892.strategy2b new file mode 100644 index 0000000..93b28f0 --- /dev/null +++ b/solutions/4.2584.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002892.strategy2b @@ -0,0 +1 @@ +{"seed": 2584, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!necronomiconei!ia! ia!ia! ia!ayuggothla r'lyehyuggothlkbbei!paaei!kpkpkkkkkbdei!kkkkpkei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.2586.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002560.strategy2b b/solutions/4.2586.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002560.strategy2b new file mode 100644 index 0000000..2c8f174 --- /dev/null +++ b/solutions/4.2586.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002560.strategy2b @@ -0,0 +1 @@ +{"seed": 2586, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!ei! r'lyehjohn bigbooteia! ia!ia! ia!bblei!lkpakblbei!kpp r'lyeh", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.26137.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002078.strategy2b b/solutions/4.26137.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002078.strategy2b new file mode 100644 index 0000000..ce8da11 --- /dev/null +++ b/solutions/4.26137.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002078.strategy2b @@ -0,0 +1 @@ +{"seed": 26137, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!john bigbooteei!aei!pkaddbkbbdpdaadlkbbbei!kei!l", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.26153.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002040.strategy2b b/solutions/4.26153.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002040.strategy2b new file mode 100644 index 0000000..b8e6628 --- /dev/null +++ b/solutions/4.26153.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002040.strategy2b @@ -0,0 +1 @@ +{"seed": 26153, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconei!akia! ia!kaplbblblkdbkbdbdei!l", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.26930.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001712.strategy2b b/solutions/4.26930.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001712.strategy2b new file mode 100644 index 0000000..70a0e0f --- /dev/null +++ b/solutions/4.26930.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001712.strategy2b @@ -0,0 +1 @@ +{"seed": 26930, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteei!akia! ia!alei!akallalaaei!kei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.28635.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002808.strategy2b b/solutions/4.28635.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002808.strategy2b new file mode 100644 index 0000000..df3beab --- /dev/null +++ b/solutions/4.28635.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002808.strategy2b @@ -0,0 +1 @@ +{"seed": 28635, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconkapia! ia!ei!abdbblblkbbei!pppaei!dllaei!dbblei!ppkaakllyogsothothyuggothl", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.28921.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002144.strategy2b b/solutions/4.28921.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002144.strategy2b new file mode 100644 index 0000000..c884074 --- /dev/null +++ b/solutions/4.28921.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002144.strategy2b @@ -0,0 +1 @@ +{"seed": 28921, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!john bigbooteei!ia! ia!ia! ia!necronomiconbei!aapakpp r'lyeh", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.2895.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002352.strategy2b b/solutions/4.2895.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002352.strategy2b new file mode 100644 index 0000000..6523962 --- /dev/null +++ b/solutions/4.2895.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002352.strategy2b @@ -0,0 +1 @@ +{"seed": 2895, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconyuggothkbldlei!bbei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.29697.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002362.strategy2b b/solutions/4.29697.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002362.strategy2b new file mode 100644 index 0000000..7c8232c --- /dev/null +++ b/solutions/4.29697.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002362.strategy2b @@ -0,0 +1 @@ +{"seed": 29697, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!ayuggothei!apakei!lei!lklaldyuggoth", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.29707.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001716.strategy2b b/solutions/4.29707.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001716.strategy2b new file mode 100644 index 0000000..4834847 --- /dev/null +++ b/solutions/4.29707.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001716.strategy2b @@ -0,0 +1 @@ +{"seed": 29707, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconei!aei!abei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.29971.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002404.strategy2b b/solutions/4.29971.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002404.strategy2b new file mode 100644 index 0000000..ccdb532 --- /dev/null +++ b/solutions/4.29971.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002404.strategy2b @@ -0,0 +1 @@ +{"seed": 29971, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ia! ia!aklb r'lyehppkpakblabbbei!ppkl", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.30014.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002040.strategy2b b/solutions/4.30014.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002040.strategy2b new file mode 100644 index 0000000..1df9b6b --- /dev/null +++ b/solutions/4.30014.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002040.strategy2b @@ -0,0 +1 @@ +{"seed": 30014, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothyuggothei!dpdpkaaayuggothlalkkkkkei!kkkkkei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.31051.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002404.strategy2b b/solutions/4.31051.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002404.strategy2b new file mode 100644 index 0000000..c6da26c --- /dev/null +++ b/solutions/4.31051.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002404.strategy2b @@ -0,0 +1 @@ +{"seed": 31051, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!necronomiconei!pd r'lyehbei!dpkaaadpdpkkpkkkpkei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.32001.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002728.strategy2b b/solutions/4.32001.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002728.strategy2b new file mode 100644 index 0000000..dc4bb89 --- /dev/null +++ b/solutions/4.32001.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002728.strategy2b @@ -0,0 +1 @@ +{"seed": 32001, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteia! ia!necronomiconyogsothothyuggothei!necronomiconkaadlbbei!bbei!paakei!lalkei!dbei!alkaei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.6045.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002394.strategy2b b/solutions/4.6045.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002394.strategy2b new file mode 100644 index 0000000..49cf2fd --- /dev/null +++ b/solutions/4.6045.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002394.strategy2b @@ -0,0 +1 @@ +{"seed": 6045, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ei!ia! ia!kadlei!dblbllkbbei!bbei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.6532.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002398.strategy2b b/solutions/4.6532.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002398.strategy2b new file mode 100644 index 0000000..4f3c9ec --- /dev/null +++ b/solutions/4.6532.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002398.strategy2b @@ -0,0 +1 @@ +{"seed": 6532, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!ia! ia!ia! ia!lbbdllkbbei!pkpkkkpkei!kei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.7533.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002714.strategy2b b/solutions/4.7533.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002714.strategy2b new file mode 100644 index 0000000..aae201d --- /dev/null +++ b/solutions/4.7533.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002714.strategy2b @@ -0,0 +1 @@ +{"seed": 7533, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconyuggothia! ia!john bigbooteei!klkakpkklbbei!bbei!l", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.8269.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002690.strategy2b b/solutions/4.8269.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002690.strategy2b new file mode 100644 index 0000000..90d9173 --- /dev/null +++ b/solutions/4.8269.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002690.strategy2b @@ -0,0 +1 @@ +{"seed": 8269, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothyuggothia! ia!necronomiconbppaayuggothei!papkei!addbkbkaei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.8444.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002382.strategy2b b/solutions/4.8444.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002382.strategy2b new file mode 100644 index 0000000..8124290 --- /dev/null +++ b/solutions/4.8444.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002382.strategy2b @@ -0,0 +1 @@ +{"seed": 8444, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!john bigbooteyogsothothei!abei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.8466.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002754.strategy2b b/solutions/4.8466.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002754.strategy2b new file mode 100644 index 0000000..623b2e9 --- /dev/null +++ b/solutions/4.8466.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002754.strategy2b @@ -0,0 +1 @@ +{"seed": 8466, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ei!ia! ia!ia! ia!kanecronomiconyuggothei!lbbei!bbei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/4.8700.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002552.strategy2b b/solutions/4.8700.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002552.strategy2b new file mode 100644 index 0000000..6e62800 --- /dev/null +++ b/solutions/4.8700.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002552.strategy2b @@ -0,0 +1 @@ +{"seed": 8700, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!ia! ia!john bigbooteei!necronomiconapaaei!abkppaakbpddddpdbbei!ei!", "problemId": 4} \ No newline at end of file diff --git a/solutions/5.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002355.strategy2b b/solutions/5.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002355.strategy2b new file mode 100644 index 0000000..6bfe404 --- /dev/null +++ b/solutions/5.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002355.strategy2b @@ -0,0 +1 @@ +{"seed": 0, "tag": "strategy2b", "solution": "necronomiconjohn bigbooteyogsothothyuggothia! ia! r'lyehei!necronomiconyogsothothkei!kklei!akpia! ia!kkei!kpdpkaaadpkkpkkkkkpdpkpdpkpaklalalalayuggothkkei!l", "problemId": 5} \ No newline at end of file diff --git a/solutions/5.11460.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001695.strategy2b b/solutions/5.11460.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001695.strategy2b new file mode 100644 index 0000000..51bf968 --- /dev/null +++ b/solutions/5.11460.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001695.strategy2b @@ -0,0 +1 @@ +{"seed": 11460, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.kkkei!adpaei!ppakpaaalakpkalayuggothyogsothoth", "problemId": 5} \ No newline at end of file diff --git a/solutions/5.14027.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002073.strategy2b b/solutions/5.14027.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002073.strategy2b new file mode 100644 index 0000000..7c4913a --- /dev/null +++ b/solutions/5.14027.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002073.strategy2b @@ -0,0 +1 @@ +{"seed": 14027, "tag": "strategy2b", "solution": "necronomiconph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothei! r'lyehei!adpadei!akkkkkappkaadppkpkkkkkpppppkaalalalalalei!lkkkkkei!", "problemId": 5} \ No newline at end of file diff --git a/solutions/5.15215.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002004.strategy2b b/solutions/5.15215.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002004.strategy2b new file mode 100644 index 0000000..ad3c76f --- /dev/null +++ b/solutions/5.15215.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002004.strategy2b @@ -0,0 +1 @@ +{"seed": 15215, "tag": "strategy2b", "solution": "john bigbootenecronomiconyogsothoth r'lyehei!ia! ia!ddia! ia!ia! ia!kdapakpppaei!dpdpkppkaaapkallljohn bigbooteei!l", "problemId": 5} \ No newline at end of file diff --git a/solutions/5.15577.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002326.strategy2b b/solutions/5.15577.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002326.strategy2b new file mode 100644 index 0000000..dd2801f --- /dev/null +++ b/solutions/5.15577.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002326.strategy2b @@ -0,0 +1 @@ +{"seed": 15577, "tag": "strategy2b", "solution": "john bigbootenecronomiconyogsothothia! ia!yuggoth r'lyehei!ia! ia!ei! r'lyehei!ppdia! ia!pppdaaei!klkkkei!", "problemId": 5} \ No newline at end of file diff --git a/solutions/5.22837.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002358.strategy2b b/solutions/5.22837.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002358.strategy2b new file mode 100644 index 0000000..f1d3f18 --- /dev/null +++ b/solutions/5.22837.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002358.strategy2b @@ -0,0 +1 @@ +{"seed": 22837, "tag": "strategy2b", "solution": "necronomiconjohn bigbooteyogsothothia! ia!yuggoth r'lyehei!ia! ia!akpaldbei!dbblbei!akkbkbdbbbnecronomiconlyogsothoth r'lyehpdei!l", "problemId": 5} \ No newline at end of file diff --git a/solutions/5.24851.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002346.strategy2b b/solutions/5.24851.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002346.strategy2b new file mode 100644 index 0000000..1f713ae --- /dev/null +++ b/solutions/5.24851.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002346.strategy2b @@ -0,0 +1 @@ +{"seed": 24851, "tag": "strategy2b", "solution": "john bigbootenecronomiconyogsothothyuggothia! ia!a r'lyehei!necronomiconia! ia!kbdbbdlei!bdbbbdllldadbbbdnecronomiconia! ia!kkei!l", "problemId": 5} \ No newline at end of file diff --git a/solutions/5.32620.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002022.strategy2b b/solutions/5.32620.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002022.strategy2b new file mode 100644 index 0000000..6bdd3e8 --- /dev/null +++ b/solutions/5.32620.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002022.strategy2b @@ -0,0 +1 @@ +{"seed": 32620, "tag": "strategy2b", "solution": "john bigbootenecronomiconyogsothothia! ia! r'lyehei!john bigbooteei!apaklaaddddpppabddpkpddkkkbdbbdlllakbbbbdnecronomiconia! ia!kkei!l", "problemId": 5} \ No newline at end of file diff --git a/solutions/5.32719.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001942.strategy2b b/solutions/5.32719.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001942.strategy2b new file mode 100644 index 0000000..f8302a7 --- /dev/null +++ b/solutions/5.32719.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001942.strategy2b @@ -0,0 +1 @@ +{"seed": 32719, "tag": "strategy2b", "solution": "necronomiconjohn bigbooteyogsothothia! ia!yuggothei!kkei!kbei!ldei!", "problemId": 5} \ No newline at end of file diff --git a/solutions/6.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002454.strategy2b b/solutions/6.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002454.strategy2b new file mode 100644 index 0000000..a5788c3 --- /dev/null +++ b/solutions/6.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002454.strategy2b @@ -0,0 +1 @@ +{"seed": 0, "tag": "strategy2b", "solution": "ia! ia!ia! ia!john bigbootenecronomiconyuggothyogsothoth r'lyehei!john bigbooteia! ia!john bigbooteyogsothothjohn bigbootejohn bigbooteia! ia!lia! ia!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.10919.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002973.strategy2b b/solutions/6.10919.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002973.strategy2b new file mode 100644 index 0000000..c2eaf8d --- /dev/null +++ b/solutions/6.10919.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002973.strategy2b @@ -0,0 +1 @@ +{"seed": 10919, "tag": "strategy2b", "solution": "ia! ia!john bigbooteyogsothothnecronomiconei!john bigbooteyuggothph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconnecronomiconia! ia!ia! ia!dlei!blbbkkbei!ppia! ia!ei!kkbkppkei!kkbk r'lyehpl", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.11993.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002142.strategy2b b/solutions/6.11993.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002142.strategy2b new file mode 100644 index 0000000..04ff15c --- /dev/null +++ b/solutions/6.11993.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002142.strategy2b @@ -0,0 +1 @@ +{"seed": 11993, "tag": "strategy2b", "solution": "ia! ia!john bigbootenecronomicon r'lyehei!ia! ia!ia! ia!john bigbooteyogsothothnecronomiconjohn bigbootenecronomicondia! ia!ia! ia!ia! ia!aei!dplabddpddei!lblaaaaei!aei!l", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.13120.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002466.strategy2b b/solutions/6.13120.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002466.strategy2b new file mode 100644 index 0000000..a8bdb5c --- /dev/null +++ b/solutions/6.13120.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002466.strategy2b @@ -0,0 +1 @@ +{"seed": 13120, "tag": "strategy2b", "solution": "ia! ia!john bigbootenecronomiconyogsothothyuggothei!john bigboote r'lyehjohn bigbootenecronomiconyogsothothia! ia!john bigbooteia! ia!ia! ia! r'lyehkkbdbbei!lkkbkbei!pkei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.13185.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001980.strategy2b b/solutions/6.13185.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001980.strategy2b new file mode 100644 index 0000000..f3ad051 --- /dev/null +++ b/solutions/6.13185.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001980.strategy2b @@ -0,0 +1 @@ +{"seed": 13185, "tag": "strategy2b", "solution": "ia! ia!john bigbootenecronomiconyogsothoth r'lyehpbbei!pa r'lyehei! r'lyehpkkei!l", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.13859.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002529.strategy2b b/solutions/6.13859.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002529.strategy2b new file mode 100644 index 0000000..98204a5 --- /dev/null +++ b/solutions/6.13859.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002529.strategy2b @@ -0,0 +1 @@ +{"seed": 13859, "tag": "strategy2b", "solution": "ia! ia!john bigbooteyogsothothnecronomiconei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ia! ia!ddbkkbei!kpdpkpkddbkei!ddbdei!ddpdei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.14118.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002457.strategy2b b/solutions/6.14118.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002457.strategy2b new file mode 100644 index 0000000..d671f2a --- /dev/null +++ b/solutions/6.14118.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002457.strategy2b @@ -0,0 +1 @@ +{"seed": 14118, "tag": "strategy2b", "solution": "ia! ia!john bigbooteyogsothothnecronomiconph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ei!ia! ia!john bigbootenecronomiconnecronomiconddia! ia!akaaakkbkkkei!kaaakei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.1519.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002351.strategy2b b/solutions/6.1519.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002351.strategy2b new file mode 100644 index 0000000..8d57e53 --- /dev/null +++ b/solutions/6.1519.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002351.strategy2b @@ -0,0 +1 @@ +{"seed": 1519, "tag": "strategy2b", "solution": "ia! ia!john bigbootenecronomiconyogsothothyuggothei! r'lyehnecronomiconnecronomicondkei!ia! ia!aaa r'lyehp r'lyeh", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.15379.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002369.strategy2b b/solutions/6.15379.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002369.strategy2b new file mode 100644 index 0000000..d76ca69 --- /dev/null +++ b/solutions/6.15379.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002369.strategy2b @@ -0,0 +1 @@ +{"seed": 15379, "tag": "strategy2b", "solution": "ia! ia!john bigbootenecronomiconyuggothyogsothothei! r'lyehnecronomiconia! ia!john bigbooteyuggothia! ia!ia! ia!aei!lei!abei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.15671.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002039.strategy2b b/solutions/6.15671.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002039.strategy2b new file mode 100644 index 0000000..f0a097d --- /dev/null +++ b/solutions/6.15671.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002039.strategy2b @@ -0,0 +1 @@ +{"seed": 15671, "tag": "strategy2b", "solution": "ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteei!necronomiconei!aei!pkei!kei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.16393.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002736.strategy2b b/solutions/6.16393.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002736.strategy2b new file mode 100644 index 0000000..4e6c443 --- /dev/null +++ b/solutions/6.16393.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002736.strategy2b @@ -0,0 +1 @@ +{"seed": 16393, "tag": "strategy2b", "solution": "ia! ia!john bigbooteyogsothothph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconei!pnecronomiconnecronomiconyuggothbbei!bbblei!aei!pbbbbldpdei!dei!l", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.16650.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002416.strategy2b b/solutions/6.16650.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002416.strategy2b new file mode 100644 index 0000000..2f2e241 --- /dev/null +++ b/solutions/6.16650.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002416.strategy2b @@ -0,0 +1 @@ +{"seed": 16650, "tag": "strategy2b", "solution": "ia! ia!ia! ia!john bigbooteyogsothothnecronomicon r'lyehyuggothei!ia! ia!john bigbooteyuggothnecronomiconei!ia! ia!ia! ia!ia! ia!aei!pkkbdbklllk r'lyehpl", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.16903.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002398.strategy2b b/solutions/6.16903.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002398.strategy2b new file mode 100644 index 0000000..1fdd330 --- /dev/null +++ b/solutions/6.16903.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002398.strategy2b @@ -0,0 +1 @@ +{"seed": 16903, "tag": "strategy2b", "solution": "ia! ia!john bigbooteyogsothothnecronomiconyuggoth r'lyehei!john bigbootejohn bigbooteyogsothoth r'lyehnecronomiconei!ldppaakei!lalei!kbkbk r'lyeh", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.17013.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002129.strategy2b b/solutions/6.17013.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002129.strategy2b new file mode 100644 index 0000000..1ba0330 --- /dev/null +++ b/solutions/6.17013.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002129.strategy2b @@ -0,0 +1 @@ +{"seed": 17013, "tag": "strategy2b", "solution": "ia! ia!ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconei!john bigboote r'lyehia! ia!abbei!ppaalei!ppaaaei!ppaakei!pppdddei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.17114.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002946.strategy2b b/solutions/6.17114.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002946.strategy2b new file mode 100644 index 0000000..1a3e6b5 --- /dev/null +++ b/solutions/6.17114.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002946.strategy2b @@ -0,0 +1 @@ +{"seed": 17114, "tag": "strategy2b", "solution": "ia! ia!john bigbooteyogsothothei!john bigbootenecronomiconph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ia! ia!john bigbootejohn bigbootejohn bigbooteia! ia!ia! ia!alklakkei!ppaaei!ei!pdkei!ppakyuggoth", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.18093.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002443.strategy2b b/solutions/6.18093.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002443.strategy2b new file mode 100644 index 0000000..c237d98 --- /dev/null +++ b/solutions/6.18093.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002443.strategy2b @@ -0,0 +1 @@ +{"seed": 18093, "tag": "strategy2b", "solution": "ia! ia!ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconjohn bigbooteyuggothei! r'lyehpklkbnecronomiconaei!ia! ia!ei!apaei!lbei!aaei!a", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.18588.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002168.strategy2b b/solutions/6.18588.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002168.strategy2b new file mode 100644 index 0000000..18ac75b --- /dev/null +++ b/solutions/6.18588.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002168.strategy2b @@ -0,0 +1 @@ +{"seed": 18588, "tag": "strategy2b", "solution": "ia! ia!ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconjohn bigbooteei!john bigbooteia! ia!necronomiconia! ia!ia! ia!ia! ia!lei!akei!laaei!aei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.19086.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002056.strategy2b b/solutions/6.19086.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002056.strategy2b new file mode 100644 index 0000000..1d1c7f8 --- /dev/null +++ b/solutions/6.19086.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002056.strategy2b @@ -0,0 +1 @@ +{"seed": 19086, "tag": "strategy2b", "solution": "ia! ia!john bigboote r'lyehei!john bigbootenecronomiconyogsothothnecronomiconjohn bigbooteei!kei!ia! ia!aia! ia!lei!l", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.21458.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002317.strategy2b b/solutions/6.21458.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002317.strategy2b new file mode 100644 index 0000000..1f7b8c0 --- /dev/null +++ b/solutions/6.21458.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002317.strategy2b @@ -0,0 +1 @@ +{"seed": 21458, "tag": "strategy2b", "solution": "ia! ia!john bigbootenecronomicon r'lyehei!john bigbooteyogsothothyuggothnecronomiconia! ia!laap", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.21728.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002844.strategy2b b/solutions/6.21728.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002844.strategy2b new file mode 100644 index 0000000..835561d --- /dev/null +++ b/solutions/6.21728.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002844.strategy2b @@ -0,0 +1 @@ +{"seed": 21728, "tag": "strategy2b", "solution": "ia! ia!ia! ia!john bigboote r'lyehei!john bigbootenecronomiconyogsothothyuggothph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.yogsothothia! ia!john bigbooteei!ia! ia!ddia! ia!lei!pppddei!kkkyuggoth", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.22079.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002785.strategy2b b/solutions/6.22079.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002785.strategy2b new file mode 100644 index 0000000..d1fe20b --- /dev/null +++ b/solutions/6.22079.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002785.strategy2b @@ -0,0 +1 @@ +{"seed": 22079, "tag": "strategy2b", "solution": "ia! ia!john bigbooteyogsothothei!john bigbootenecronomicon r'lyehia! ia!john bigbootenecronomiconnecronomiconph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.lyuggoth", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.23220.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002474.strategy2b b/solutions/6.23220.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002474.strategy2b new file mode 100644 index 0000000..ad2aad1 --- /dev/null +++ b/solutions/6.23220.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002474.strategy2b @@ -0,0 +1 @@ +{"seed": 23220, "tag": "strategy2b", "solution": "ia! ia!ia! ia!john bigbooteyogsothothnecronomiconei! r'lyehph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteia! ia!aei!ddia! ia!ia! ia!adddppaei!kkei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.23256.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002453.strategy2b b/solutions/6.23256.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002453.strategy2b new file mode 100644 index 0000000..4d52a9c --- /dev/null +++ b/solutions/6.23256.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002453.strategy2b @@ -0,0 +1 @@ +{"seed": 23256, "tag": "strategy2b", "solution": "ia! ia!john bigbooteyogsothothph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconei!ia! ia!john bigbootenecronomiconei!aei!pia! ia!paaei!lei!aei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.24334.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001977.strategy2b b/solutions/6.24334.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001977.strategy2b new file mode 100644 index 0000000..5b858d0 --- /dev/null +++ b/solutions/6.24334.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001977.strategy2b @@ -0,0 +1 @@ +{"seed": 24334, "tag": "strategy2b", "solution": "ia! ia!john bigbootenecronomicon r'lyehyogsothothei! r'lyehpdkakbbb r'lyehpdei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.24513.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002407.strategy2b b/solutions/6.24513.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002407.strategy2b new file mode 100644 index 0000000..87af079 --- /dev/null +++ b/solutions/6.24513.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002407.strategy2b @@ -0,0 +1 @@ +{"seed": 24513, "tag": "strategy2b", "solution": "ia! ia!ia! ia!john bigboote r'lyehei!john bigbootenecronomiconyogsothothyuggothjohn bigbooteyogsothothjohn bigbooteia! ia!ia! ia!dbei!dei!aei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.24524.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002306.strategy2b b/solutions/6.24524.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002306.strategy2b new file mode 100644 index 0000000..dde9239 --- /dev/null +++ b/solutions/6.24524.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002306.strategy2b @@ -0,0 +1 @@ +{"seed": 24524, "tag": "strategy2b", "solution": "ia! ia!john bigbootenecronomicon r'lyehyogsothothei!john bigboote r'lyehpaayuggoth r'lyehpl", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.24732.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002770.strategy2b b/solutions/6.24732.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002770.strategy2b new file mode 100644 index 0000000..a2e54f4 --- /dev/null +++ b/solutions/6.24732.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002770.strategy2b @@ -0,0 +1 @@ +{"seed": 24732, "tag": "strategy2b", "solution": "ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconyuggothei!ia! ia!necronomiconnecronomiconia! ia!alkbdbei!bbei!ppaalbbbbblaia! ia!l", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.25267.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002824.strategy2b b/solutions/6.25267.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002824.strategy2b new file mode 100644 index 0000000..045a288 --- /dev/null +++ b/solutions/6.25267.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002824.strategy2b @@ -0,0 +1 @@ +{"seed": 25267, "tag": "strategy2b", "solution": "ia! ia!john bigbooteyogsothothph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconei!john bigbooteyuggothnecronomiconjohn bigbooteia! ia!ia! ia!ia! ia!ia! ia!dbei!bbbllkei!ddbdddei!lei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.25460.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002841.strategy2b b/solutions/6.25460.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002841.strategy2b new file mode 100644 index 0000000..fae0b65 --- /dev/null +++ b/solutions/6.25460.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002841.strategy2b @@ -0,0 +1 @@ +{"seed": 25460, "tag": "strategy2b", "solution": "ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconyogsothothjohn bigbooteei!john bigbooteyuggothldpia! ia!ia! ia!aabkpdpkpapkaei!kpdpkkei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.25499.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002487.strategy2b b/solutions/6.25499.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002487.strategy2b new file mode 100644 index 0000000..83430c6 --- /dev/null +++ b/solutions/6.25499.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002487.strategy2b @@ -0,0 +1 @@ +{"seed": 25499, "tag": "strategy2b", "solution": "ia! ia!john bigboote r'lyehei!ia! ia!ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconnecronomiconia! ia!ia! ia!ia! ia! r'lyehia! ia!pkei!bblyuggoth", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.25536.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002430.strategy2b b/solutions/6.25536.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002430.strategy2b new file mode 100644 index 0000000..fae2d1d --- /dev/null +++ b/solutions/6.25536.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002430.strategy2b @@ -0,0 +1 @@ +{"seed": 25536, "tag": "strategy2b", "solution": "ia! ia!ia! ia!john bigbooteyogsothothyuggothnecronomicon r'lyehei!necronomiconyogsothothyogsothothyuggothnecronomiconia! ia!ia! ia!kdlkbbei!pppdlaei!pppaabllaaei!aei!ppkl", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.26670.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002386.strategy2b b/solutions/6.26670.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002386.strategy2b new file mode 100644 index 0000000..0571ccd --- /dev/null +++ b/solutions/6.26670.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002386.strategy2b @@ -0,0 +1 @@ +{"seed": 26670, "tag": "strategy2b", "solution": "ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconei!ia! ia! r'lyehyuggothdbei!aei!pakkkei!l", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.26708.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001954.strategy2b b/solutions/6.26708.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001954.strategy2b new file mode 100644 index 0000000..147cbfd --- /dev/null +++ b/solutions/6.26708.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001954.strategy2b @@ -0,0 +1 @@ +{"seed": 26708, "tag": "strategy2b", "solution": "ia! ia!john bigbooteyogsothothnecronomiconei! r'lyehei!ei!bei!bbbei!lei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.26906.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002042.strategy2b b/solutions/6.26906.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002042.strategy2b new file mode 100644 index 0000000..53119fd --- /dev/null +++ b/solutions/6.26906.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002042.strategy2b @@ -0,0 +1 @@ +{"seed": 26906, "tag": "strategy2b", "solution": "ia! ia!john bigbootenecronomiconph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.lei!ia! ia!bbb r'lyeh", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.28599.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002578.strategy2b b/solutions/6.28599.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002578.strategy2b new file mode 100644 index 0000000..bcf58e7 --- /dev/null +++ b/solutions/6.28599.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002578.strategy2b @@ -0,0 +1 @@ +{"seed": 28599, "tag": "strategy2b", "solution": "ia! ia!ia! ia!ia! ia!john bigbooteyogsothothnecronomicon r'lyehei!john bigbootejohn bigbooteyuggoth r'lyehyogsothothia! ia!ia! ia!ia! ia!ia! ia!llei!aei!ppdddbbbbbka r'lyehp", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.2860.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001964.strategy2b b/solutions/6.2860.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001964.strategy2b new file mode 100644 index 0000000..af757ac --- /dev/null +++ b/solutions/6.2860.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001964.strategy2b @@ -0,0 +1 @@ +{"seed": 2860, "tag": "strategy2b", "solution": "ia! ia!john bigbootenecronomiconyogsothoth r'lyehei! r'lyehbei!kei!ei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.29169.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001669.strategy2b b/solutions/6.29169.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001669.strategy2b new file mode 100644 index 0000000..a01850f --- /dev/null +++ b/solutions/6.29169.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001669.strategy2b @@ -0,0 +1 @@ +{"seed": 29169, "tag": "strategy2b", "solution": "ia! ia!john bigbootenecronomicon r'lyehei!ia! ia!john bigbooteia! ia!aei!lei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.31026.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002408.strategy2b b/solutions/6.31026.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002408.strategy2b new file mode 100644 index 0000000..5afe79c --- /dev/null +++ b/solutions/6.31026.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002408.strategy2b @@ -0,0 +1 @@ +{"seed": 31026, "tag": "strategy2b", "solution": "ia! ia!john bigbootenecronomicon r'lyehei!john bigbootenecronomiconyogsothothia! ia!ia! ia!ia! ia!ia! ia!john bigboote r'lyehpppaalabyuggothkkbdbbbdbkei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.3703.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002516.strategy2b b/solutions/6.3703.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002516.strategy2b new file mode 100644 index 0000000..3b9e001 --- /dev/null +++ b/solutions/6.3703.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002516.strategy2b @@ -0,0 +1 @@ +{"seed": 3703, "tag": "strategy2b", "solution": "ia! ia!john bigbootenecronomicon r'lyehei!john bigbootenecronomiconia! ia!ia! ia!john bigbooteyogsothothyuggothjohn bigbootenecronomiconia! ia!ia! ia!ia! ia!necronomiconia! ia!kapadpkpdpakpkpdpkdddei!l", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.5343.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002243.strategy2b b/solutions/6.5343.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002243.strategy2b new file mode 100644 index 0000000..16166fa --- /dev/null +++ b/solutions/6.5343.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002243.strategy2b @@ -0,0 +1 @@ +{"seed": 5343, "tag": "strategy2b", "solution": "ia! ia!john bigbootenecronomiconph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconei!necronomiconjohn bigbootenecronomiconia! ia!ia! ia! r'lyehia! ia!ia! ia!aei!aei!abbbei!ppaakei!lei!palei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.629.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002435.strategy2b b/solutions/6.629.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002435.strategy2b new file mode 100644 index 0000000..25efd45 --- /dev/null +++ b/solutions/6.629.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002435.strategy2b @@ -0,0 +1 @@ +{"seed": 629, "tag": "strategy2b", "solution": "ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!necronomiconyogsothothjohn bigbooteyuggoth r'lyehei!ia! ia!john bigbootejohn bigbooteia! ia! r'lyehpaei!akkpkei!kei!l", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.6839.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002483.strategy2b b/solutions/6.6839.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002483.strategy2b new file mode 100644 index 0000000..5105ebb --- /dev/null +++ b/solutions/6.6839.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002483.strategy2b @@ -0,0 +1 @@ +{"seed": 6839, "tag": "strategy2b", "solution": "ia! ia!ia! ia!ia! ia!john bigbootenecronomicon r'lyehei!john bigbooteyogsothothph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconia! ia!aei!ei!kbbei!ppakei!kei!l", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.7082.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002383.strategy2b b/solutions/6.7082.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002383.strategy2b new file mode 100644 index 0000000..b1ef626 --- /dev/null +++ b/solutions/6.7082.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002383.strategy2b @@ -0,0 +1 @@ +{"seed": 7082, "tag": "strategy2b", "solution": "ia! ia!john bigbooteyogsothothnecronomicon r'lyehei!john bigbooteyuggothyogsothothyogsothothyogsothothia! ia!ia! ia!kpakdbddppklblia! ia!aa", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.7610.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002810.strategy2b b/solutions/6.7610.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002810.strategy2b new file mode 100644 index 0000000..46e8062 --- /dev/null +++ b/solutions/6.7610.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002810.strategy2b @@ -0,0 +1 @@ +{"seed": 7610, "tag": "strategy2b", "solution": "ia! ia!john bigbooteyogsothothnecronomiconei!ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconjohn bigbooteyuggothnecronomiconbbei!ia! ia!pia! ia!aei!aei!apkei!kkbbdllaei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.8123.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002380.strategy2b b/solutions/6.8123.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002380.strategy2b new file mode 100644 index 0000000..15b7be7 --- /dev/null +++ b/solutions/6.8123.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002380.strategy2b @@ -0,0 +1 @@ +{"seed": 8123, "tag": "strategy2b", "solution": "ia! ia!ia! ia!john bigbooteyogsothothnecronomiconei!necronomiconyuggoth r'lyeh r'lyehia! ia!ia! ia!ia! ia!aei!aei!apkei!akppaei!pkl", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.8466.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002393.strategy2b b/solutions/6.8466.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002393.strategy2b new file mode 100644 index 0000000..bf492ee --- /dev/null +++ b/solutions/6.8466.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002393.strategy2b @@ -0,0 +1 @@ +{"seed": 8466, "tag": "strategy2b", "solution": "ia! ia!john bigbootenecronomicon r'lyehyogsothothyuggothei!necronomiconnecronomiconyogsothothyogsothoth r'lyehei!dei!bei!bbbllei!bbbdbei!kei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.8780.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002486.strategy2b b/solutions/6.8780.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002486.strategy2b new file mode 100644 index 0000000..17c9d76 --- /dev/null +++ b/solutions/6.8780.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002486.strategy2b @@ -0,0 +1 @@ +{"seed": 8780, "tag": "strategy2b", "solution": "ia! ia!john bigbooteyogsothothei!john bigbootenecronomicon r'lyehia! ia!john bigbooteyuggothnecronomiconia! ia!john bigbooteia! ia!ia! ia! r'lyehia! ia!ia! ia! r'lyehei!kei!kkbdbkkei!ppkei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.8856.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002444.strategy2b b/solutions/6.8856.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002444.strategy2b new file mode 100644 index 0000000..e59466c --- /dev/null +++ b/solutions/6.8856.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002444.strategy2b @@ -0,0 +1 @@ +{"seed": 8856, "tag": "strategy2b", "solution": "ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconei!john bigbooteyuggothia! ia!necronomiconbbei!ia! ia!abppppdlakbei!kkbkbdei!", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.9536.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002444.strategy2b b/solutions/6.9536.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002444.strategy2b new file mode 100644 index 0000000..5845b57 --- /dev/null +++ b/solutions/6.9536.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002444.strategy2b @@ -0,0 +1 @@ +{"seed": 9536, "tag": "strategy2b", "solution": "ia! ia!john bigboote r'lyehei!john bigbooteyuggothia! ia!john bigbootenecronomiconyogsothothjohn bigbooteyogsothothnecronomiconkyuggothia! ia!aei!kp r'lyeh", "problemId": 6} \ No newline at end of file diff --git a/solutions/6.9816.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002384.strategy2b b/solutions/6.9816.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002384.strategy2b new file mode 100644 index 0000000..38d9031 --- /dev/null +++ b/solutions/6.9816.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002384.strategy2b @@ -0,0 +1 @@ +{"seed": 9816, "tag": "strategy2b", "solution": "ia! ia!john bigbootenecronomicon r'lyehyogsothothyuggothei!necronomiconjohn bigbootenecronomiconia! ia!ia! ia! r'lyehei!d r'lyeh", "problemId": 6} \ No newline at end of file diff --git a/solutions/7.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001719.strategy2b b/solutions/7.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001719.strategy2b new file mode 100644 index 0000000..f721393 --- /dev/null +++ b/solutions/7.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001719.strategy2b @@ -0,0 +1 @@ +{"seed": 0, "tag": "strategy2b", "solution": "necronomiconph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconadbbbbdllei!kbldllllayogsothoth", "problemId": 7} \ No newline at end of file diff --git a/solutions/7.16651.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002292.strategy2b b/solutions/7.16651.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002292.strategy2b new file mode 100644 index 0000000..1d6a74d --- /dev/null +++ b/solutions/7.16651.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002292.strategy2b @@ -0,0 +1 @@ +{"seed": 16651, "tag": "strategy2b", "solution": "necronomiconjohn bigbooteyogsothothia! ia! r'lyehyuggothei!ablddbdbdlllyuggothaaakla r'lyeh r'lyehpl", "problemId": 7} \ No newline at end of file diff --git a/solutions/7.18705.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002278.strategy2b b/solutions/7.18705.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002278.strategy2b new file mode 100644 index 0000000..8c9ede1 --- /dev/null +++ b/solutions/7.18705.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002278.strategy2b @@ -0,0 +1 @@ +{"seed": 18705, "tag": "strategy2b", "solution": "necronomiconyogsothothjohn bigbooteyuggoth r'lyehei!ia! ia!pdia! ia!akei!kkei!kbbdbkbdei!dei!", "problemId": 7} \ No newline at end of file diff --git a/solutions/7.22828.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002068.strategy2b b/solutions/7.22828.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002068.strategy2b new file mode 100644 index 0000000..aed2650 --- /dev/null +++ b/solutions/7.22828.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000002068.strategy2b @@ -0,0 +1 @@ +{"seed": 22828, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconia! ia!ia! ia!ei!kblei!kpkakdbkbdbnecronomiconllalayuggothei!kkei!l", "problemId": 7} \ No newline at end of file diff --git a/solutions/7.27669.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001735.strategy2b b/solutions/7.27669.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001735.strategy2b new file mode 100644 index 0000000..de3d07d --- /dev/null +++ b/solutions/7.27669.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001735.strategy2b @@ -0,0 +1 @@ +{"seed": 27669, "tag": "strategy2b", "solution": "ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ia! ia!ia! ia! r'lyehei!paakdpapkpia! ia!adpadalalayuggothdei!l", "problemId": 7} \ No newline at end of file diff --git a/solutions/8.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001057.strategy2b b/solutions/8.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001057.strategy2b new file mode 100644 index 0000000..3526408 --- /dev/null +++ b/solutions/8.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001057.strategy2b @@ -0,0 +1 @@ +{"seed": 0, "tag": "strategy2b", "solution": "john bigbooteei!ia! ia!ei!ia! ia!abppia! ia!pabpppaaei!pppaappppalei!pppalbei!pppalbbei!pppalbbbei!pppalbbbbei!pppalbbbbbbei!aei!abbbei!", "problemId": 8} \ No newline at end of file diff --git a/solutions/8.10596.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001728.strategy2b b/solutions/8.10596.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001728.strategy2b new file mode 100644 index 0000000..fbea994 --- /dev/null +++ b/solutions/8.10596.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001728.strategy2b @@ -0,0 +1 @@ +{"seed": 10596, "tag": "strategy2b", "solution": "necronomiconia! ia!ia! ia!ia! ia!ia! ia! r'lyehyuggothei!ia! ia!necronomiconia! ia!ia! ia!lia! ia!", "problemId": 8} \ No newline at end of file diff --git a/solutions/8.14104.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001041.strategy2b b/solutions/8.14104.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001041.strategy2b new file mode 100644 index 0000000..bf3137a --- /dev/null +++ b/solutions/8.14104.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001041.strategy2b @@ -0,0 +1 @@ +{"seed": 14104, "tag": "strategy2b", "solution": "john bigbootebbei!bei!ia! ia!pia! ia!abppia! ia!pabpppaaei!pppaappppalei!pppalbei!pppalbei!ppalei!ppalbpppabppppppppppppppl", "problemId": 8} \ No newline at end of file diff --git a/solutions/8.19012.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001007.strategy2b b/solutions/8.19012.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001007.strategy2b new file mode 100644 index 0000000..288c4b1 --- /dev/null +++ b/solutions/8.19012.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001007.strategy2b @@ -0,0 +1 @@ +{"seed": 19012, "tag": "strategy2b", "solution": "john bigbooteei!ia! ia!ei!ia! ia!abppia! ia!paaablei!aei!l", "problemId": 8} \ No newline at end of file diff --git a/solutions/8.20240.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001007.strategy2b b/solutions/8.20240.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001007.strategy2b new file mode 100644 index 0000000..b5ccff5 --- /dev/null +++ b/solutions/8.20240.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001007.strategy2b @@ -0,0 +1 @@ +{"seed": 20240, "tag": "strategy2b", "solution": "john bigbooteei!ia! ia!ei!ia! ia!abppia! ia!paaablei!aei!l", "problemId": 8} \ No newline at end of file diff --git a/solutions/8.2629.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001159.strategy2b b/solutions/8.2629.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001159.strategy2b new file mode 100644 index 0000000..961d8c7 --- /dev/null +++ b/solutions/8.2629.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001159.strategy2b @@ -0,0 +1 @@ +{"seed": 2629, "tag": "strategy2b", "solution": "necronomiconia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ei!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ei!aei!ei!abppia! ia!papaei!", "problemId": 8} \ No newline at end of file diff --git a/solutions/8.28581.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001377.strategy2b b/solutions/8.28581.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001377.strategy2b new file mode 100644 index 0000000..42b9897 --- /dev/null +++ b/solutions/8.28581.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001377.strategy2b @@ -0,0 +1 @@ +{"seed": 28581, "tag": "strategy2b", "solution": "necronomiconia! ia!ia! ia!ia! ia!ia! ia!john bigbooteei!ia! ia!pia! ia!aaei!lei!aei!", "problemId": 8} \ No newline at end of file diff --git a/solutions/8.4491.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001359.strategy2b b/solutions/8.4491.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001359.strategy2b new file mode 100644 index 0000000..a85857b --- /dev/null +++ b/solutions/8.4491.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001359.strategy2b @@ -0,0 +1 @@ +{"seed": 4491, "tag": "strategy2b", "solution": "necronomiconia! ia!ia! ia!ia! ia!ia! ia!john bigbooteei!ia! ia!paaei!abei!aei!", "problemId": 8} \ No newline at end of file diff --git a/solutions/8.5696.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001782.strategy2b b/solutions/8.5696.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001782.strategy2b new file mode 100644 index 0000000..09a6679 --- /dev/null +++ b/solutions/8.5696.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001782.strategy2b @@ -0,0 +1 @@ +{"seed": 5696, "tag": "strategy2b", "solution": "necronomiconia! ia!ia! ia!ia! ia!ia! ia! r'lyehyuggothei!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!aei!bei!bbei!bbbbei!aei!ppaei!aei!", "problemId": 8} \ No newline at end of file diff --git a/solutions/8.8000.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001820.strategy2b b/solutions/8.8000.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001820.strategy2b new file mode 100644 index 0000000..eb571d5 --- /dev/null +++ b/solutions/8.8000.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001820.strategy2b @@ -0,0 +1 @@ +{"seed": 8000, "tag": "strategy2b", "solution": "necronomiconia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ei!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ei!ayogsothoth r'lyehei!aei!aei!aei!bei!bbei!bbblei!aei!aei!l", "problemId": 8} \ No newline at end of file diff --git a/solutions/9.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001301.strategy2b b/solutions/9.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001301.strategy2b new file mode 100644 index 0000000..de00cf5 --- /dev/null +++ b/solutions/9.0.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001301.strategy2b @@ -0,0 +1 @@ +{"seed": 0, "tag": "strategy2b", "solution": "necronomiconyuggoth r'lyehpapakbbei!paei!ppkl", "problemId": 9} \ No newline at end of file diff --git a/solutions/9.10998.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001092.strategy2b b/solutions/9.10998.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001092.strategy2b new file mode 100644 index 0000000..952c377 --- /dev/null +++ b/solutions/9.10998.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001092.strategy2b @@ -0,0 +1 @@ +{"seed": 10998, "tag": "strategy2b", "solution": "necronomiconia! ia!kbei!bbei!ppkkbbei!ppkl", "problemId": 9} \ No newline at end of file diff --git a/solutions/9.23855.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001281.strategy2b b/solutions/9.23855.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001281.strategy2b new file mode 100644 index 0000000..5cb06bd --- /dev/null +++ b/solutions/9.23855.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001281.strategy2b @@ -0,0 +1 @@ +{"seed": 23855, "tag": "strategy2b", "solution": "necronomiconia! ia!kbei!bbbb r'lyeh", "problemId": 9} \ No newline at end of file diff --git a/solutions/9.26637.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001830.strategy2b b/solutions/9.26637.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001830.strategy2b new file mode 100644 index 0000000..a2df9d4 --- /dev/null +++ b/solutions/9.26637.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001830.strategy2b @@ -0,0 +1 @@ +{"seed": 26637, "tag": "strategy2b", "solution": "necronomiconyuggothia! ia!kbbll r'lyehppakbbei!ppkkbbei!ppkl", "problemId": 9} \ No newline at end of file diff --git a/solutions/9.4150.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001101.strategy2b b/solutions/9.4150.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001101.strategy2b new file mode 100644 index 0000000..a73ee03 --- /dev/null +++ b/solutions/9.4150.00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001101.strategy2b @@ -0,0 +1 @@ +{"seed": 4150, "tag": "strategy2b", "solution": "necronomiconia! ia!kblbbdei!bei!bbbei!ppkkbbei!ppkl", "problemId": 9} \ No newline at end of file diff --git a/submitted/10.json b/submitted/10.json index ece0e59..681a0aa 100644 --- a/submitted/10.json +++ b/submitted/10.json @@ -1 +1 @@ -[{"seed":0,"tag":"strategy2b","solution":"dei!kdei!bei!pdaei!ppdlakbbei!ppdlakei!ppdladpppddppppkppkl","problemId":10}] +[{"seed":0,"tag":"strategy2b","solution":"dei!kd r'lyeh","problemId":10}] diff --git a/submitted/11.json b/submitted/11.json index e393d21..a3cdb3a 100644 --- a/submitted/11.json +++ b/submitted/11.json @@ -1 +1 @@ -[{"seed":0,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.yuggothei!necronomiconbdpppdei!pkbbei!dei!","problemId":11},{"seed":12877,"tag":"strategy2b","solution":"cthulhu r'lyehyogsothothia! ia!ia! ia!necronomiconei!ldappdpkppdei!l","problemId":11},{"seed":16526,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconia! ia!necronomiconyogsothothyuggothei!necronomiconcthulhu r'lyehnecronomiconia! ia!ia! ia!pcthulhu r'lyehei!pei!aei!adei!kpddppaei!ddbbei!kaei!l","problemId":11},{"seed":19558,"tag":"strategy2b","solution":"cthulhu r'lyehia! ia!ia! ia!necronomiconei!aei!llei!ei!aei!aadaaddei!ayuggoth","problemId":11},{"seed":20528,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconia! ia!necronomiconei!ia! ia!necronomiconei!dei!paei!l","problemId":11}] +[{"seed":0,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!yuggothei!john bigbootejohn bigbooteyogsothoth r'lyehjohn bigboote r'lyehplkakkei!akei!kkei! r'lyehppppdei!kei!","problemId":11},{"seed":12877,"tag":"strategy2b","solution":"john bigbootenecronomiconyogsothothia! ia!necronomiconei!ia! ia!ia! ia!aaei!alei! r'lyehpkpddei!kei!l","problemId":11},{"seed":16526,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconia! ia!necronomiconyogsothothyuggothei!necronomiconcthulhu r'lyehnecronomiconia! ia!ia! ia!pcthulhu r'lyehei!pei!aei!adei!kpddppaei!ddbbei!kaei!l","problemId":11},{"seed":19558,"tag":"strategy2b","solution":"cthulhu r'lyehia! ia!ia! ia!necronomiconei!aei!llei!ei!aei!aadaaddei!ayuggoth","problemId":11},{"seed":20528,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteia! ia!john bigbooteei!ia! ia!ia! ia!aei!abbbei!aei!ia! ia!ei!aaaei!kpddei!adaabkei!","problemId":11}] diff --git a/submitted/12.json b/submitted/12.json index 2101430..6989351 100644 --- a/submitted/12.json +++ b/submitted/12.json @@ -1 +1 @@ -[{"seed":0,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconyogsothothyuggothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconei!ia! ia!acthulhu r'lyehyuggothei!aei!akei!pdpkppdei!l","problemId":12},{"seed":1155,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconyogsothothyuggothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ia! ia!necronomiconei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconei!llnecronomiconei!ia! ia!aei!ayogsothothei!aei!alkei!kei!aei!l","problemId":12},{"seed":12700,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconyogsothothyuggothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconei!necronomiconnecronomiconei!kei!kkaaei!aei!necronomiconia! ia!dei!aei!dei!kbei!","problemId":12},{"seed":18660,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconyogsothothyuggothia! ia!necronomiconei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconcthulhu r'lyehcthulhu r'lyehnecronomiconnecronomiconcthulhu r'lyehpia! ia!ia! ia!kaia! ia!ia! ia!necronomicondei!aei!dbei!","problemId":12},{"seed":19102,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconyogsothothyuggothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconia! ia!aei!llei!abei!","problemId":12},{"seed":24103,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconyogsothothyuggothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconei!ia! ia!necronomiconcthulhu r'lyehyuggothcthulhu r'lyehcthulhu r'lyehcthulhu r'lyehia! ia!ia! ia!cthulhu r'lyehyogsothothnecronomiconlllei!aallei!ablldei!aei!pdaakppkppdaei!aei!l","problemId":12},{"seed":24762,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconyogsothothyuggothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconei!necronomiconia! ia!ia! ia!ia! ia!ia! ia!lei!alalei!lei!ldei!aei!k","problemId":12},{"seed":24803,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconia! ia!adei!aei!akaei!pdaaei!pppdei!l","problemId":12},{"seed":29992,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconyogsothothyuggothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconei!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ayogsothothei!ayuggothei!aei!pppdei!kei!","problemId":12},{"seed":5864,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconyogsothothyuggothia! ia!necronomiconei!aei!allei!dei!kei!l","problemId":12}] +[{"seed":0,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootejohn bigbootejohn bigbootejohn bigbootejohn bigbootejohn bigbootejohn bigbootenecronomiconyuggothjohn bigbootejohn bigbootenecronomiconia! ia!ia! ia! r'lyehia! ia!adbbkbbbb r'lyehpl","problemId":12},{"seed":1155,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothyuggothia! ia!john bigbooteei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootejohn bigbootejohn bigbooteia! ia!necronomiconnecronomiconnecronomiconjohn bigbooteei!aaapia! ia!aei! r'lyehia! ia!l r'lyehpkei!l","problemId":12},{"seed":12700,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ia! ia!john bigbooteia! ia!aei! r'lyehpkabkyogsothothei!aei!kb r'lyehpl","problemId":12},{"seed":18660,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothyuggothia! ia!john bigbooteei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootejohn bigbooteyogsothothjohn bigbootejohn bigbootenecronomiconjohn bigbooteei!ei!ia! ia!aei!ayuggoth r'lyehpd r'lyehei!aei!dppkei!pdei!l","problemId":12},{"seed":19102,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothyuggothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteei!john bigbootejohn bigbootejohn bigbootejohn bigbootejohn bigbootejohn bigbootenecronomiconyuggothyuggoth r'lyehpkblalaaei!akaaei!akaei!pppppkbbbbbbb r'lyeh","problemId":12},{"seed":24103,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconia! ia!ia! ia!john bigbooteyuggothnecronomiconia! ia!aaa r'lyeh r'lyehei!aaei!kb r'lyehpl","problemId":12},{"seed":24762,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!john bigbooteyogsothothjohn bigbooteia! ia!ia! ia!aei!a r'lyehia! ia!alei!l r'lyeh","problemId":12},{"seed":24803,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothyuggothia! ia!pei!pia! ia!aei! r'lyehia! ia!aei!lei!l r'lyeh","problemId":12},{"seed":29992,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!john bigbooteyuggothei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootejohn bigbooteia! ia!knecronomiconaaei!lei!aei! r'lyehpaei!aei!pdpkpdppkei!l","problemId":12},{"seed":5864,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothyuggothia! ia!john bigbooteei!john bigbootejohn bigbootejohn bigbootejohn bigbooteia! ia! r'lyehia! ia!akpakpkkei!ayogsothothkia! ia!aei!aei! r'lyehpapp r'lyeh","problemId":12}] diff --git a/submitted/13.json b/submitted/13.json index d67d8f8..2855daa 100644 --- a/submitted/13.json +++ b/submitted/13.json @@ -1 +1 @@ -[{"seed":0,"tag":"strategy2","solution":"kbddbkkbddbkkbkkpddei!paalpaakpddei!ddddbkkkbkkplkkkkkbkakkkkkbkakkkkkbkkkakkkkkbkkkkkbbkpddpkkpdppkkakkei!","problemId":13}] +[{"seed":0,"tag":"strategy2b","solution":"necronomiconia! ia!john bigbooteyogsothoth r'lyehpakia! ia!ei!kkakkkpkkkkkpddddppkei!kkkbkbddddldbdddbkbkpkkbddei!kei!","problemId":13}] diff --git a/submitted/14.json b/submitted/14.json new file mode 100644 index 0000000..4bf1f40 --- /dev/null +++ b/submitted/14.json @@ -0,0 +1 @@ +[{"seed":0,"tag":"strategy2b","solution":"ia! ia!ia! ia!john bigbootenecronomiconyuggothalappkaei!pklbbbdei!dldbdlbklbdbllblkbnecronomiconyogsothoth r'lyehjohn bigbooteia! ia!john bigbooteapl","problemId":14}] diff --git a/submitted/15.json b/submitted/15.json index e9e1c78..4ee8234 100644 --- a/submitted/15.json +++ b/submitted/15.json @@ -1 +1 @@ -[{"seed":0,"tag":"strategy2","solution":"kkkkadlalddlkkkkkbkkkkkbkkkkkbkkkkkbkkblalddlkkkkkbllalakblapkpkkkkkpkkkkkppaalpaalalakblklklalakpkpaalpaalalakpkkkkkpkkkklalaakaaei!","problemId":15}] +[{"seed":0,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.bbei!ppia! ia!pppia! ia!ppabppppalalalia! ia!pppalalalaadppppalalalakppppalalkppppakppppkpkl","problemId":15}] diff --git a/submitted/16.json b/submitted/16.json index 7ebfb3b..6b3f1e1 100644 --- a/submitted/16.json +++ b/submitted/16.json @@ -1 +1 @@ -[{"seed":0,"tag":"strategy2","solution":"paalpaapaalpaapabddbkkbkpppabddbkakkkkkbkakkkkkbkkklkbplaabbei!ppabbbbbei!abbei!pabbbbei!pabei!abbbei!ppppaei!plbbbbei!lei!","problemId":16}] +[{"seed":0,"tag":"strategy2b","solution":"ia! ia!john bigbootenecronomiconia! ia!lei!bbei!bei!ppia! ia!ppppaayuggoth","problemId":16}] diff --git a/submitted/17.json b/submitted/17.json index 5b18955..11166ad 100644 --- a/submitted/17.json +++ b/submitted/17.json @@ -1 +1 @@ -[{"seed":0,"tag":"strategy2","solution":"bbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbpppppaalpaapppppaalpaabbbbbbbbbpppppaalpaabbbbbbbbbppppaalpaabbbbbbbbpppaalpaabbbbbbbppaalpaapaalpaapaalpaapaalpaapaalpaappaalpaalbbbbllbbbblbbblbbllbbbbllbbbllbbllabbbbbbbbllabbbbbbbllabbbbbbllabbbbbllabbbbllabbbllabbllapppllappllabpabpabbbbabbbbbbbbaabei!ei!","problemId":17}] +[{"seed":0,"tag":"strategy2b","solution":"ia! ia!ia! ia!ia! ia!ei!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!aia! ia!ei!ei!pia! ia!aei!pia! ia!lppia! ia!ppia! ia!pabpppia! ia!ppabppppia! ia!ppppia! ia!pppabpppppia! ia!ppppabppppppaaei!ppppppaaei!pppppaabppppppabpppppppppppppppppppppppppppppppppppl","problemId":17}] diff --git a/submitted/2.json b/submitted/2.json index 6428eff..c7df0ae 100644 --- a/submitted/2.json +++ b/submitted/2.json @@ -1 +1 @@ -[{"seed":0,"tag":"strategy2","solution":"kkbkkbkkbkkbkkbkbkkpkkpkpaalpaapaalpaadpppdpkpdlkkkkkei!kkkkkei!","problemId":2},{"seed":0,"tag":"strategy2.500M","solution":"kkbkkbkkbkkbkkbkbkkpkkpkpaalpaapaalpaakkkkbkpbdldlldbdbkbdbkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!l","problemId":2},{"seed":13639,"tag":"strategy2","solution":"kkbkkbkkbkkbkkbkbddddbkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkppaalpaakkkkpaalpaakkbddddbkkkkpkpaalpaakkkkkbkkkkkbkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkpkei!","problemId":2},{"seed":13639,"tag":"strategy2.500M","solution":"kkbkkbkkbkkbkkbkbddddbkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkppaalpaakkkkpaalpaakkbddddbkkkkpkpaalpaakkkkkbkkkkkbkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkpkei!","problemId":2},{"seed":13948,"tag":"strategy2","solution":"kkbkkbkkbkkbkkbkbkkpkkpkpaalpaapaalpaakkkkkbkkakkkkkpddpkkkkbbbbbkpdppkkkppdddbkadddpkkkkkpkpdpppkpaei!aei!","problemId":2},{"seed":13948,"tag":"strategy2.500M","solution":"kkbkkbkkbkkbkkbkbkkpkkpkpaalpaapaalpaakkkkkbkkakkkkkpddpkkkkbbbbbkpdppkkkppdddbkadddpkkkkkpkklddddbddapkdpppkkkpppdei!ppdei!ab","problemId":2},{"seed":15385,"tag":"strategy2","solution":"kkbkkbkkbkkbkkbkbkkbdbkkkkkpkkkpaalpaakpkpddddbkkakkkkkbkkkkkbkkkakkkkkbkakkkkkbkakkkkkbkkkkkbkkkbkkkkkbkkkkkbkkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpddddpkakkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkaddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddppkei!","problemId":2},{"seed":15385,"tag":"strategy2.500M","solution":"kkbkkbkkbkkbkkbkbkkbdbkkkkkpkkkpaalpaakpkpddddbkkakkkkkbkkkkkbkkkakkkkkbkakkkkkbkakkkkkbkkkkkbkkkbkkkkkbkkkkkbkkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpddddpkakkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkaddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddppkei!","problemId":2},{"seed":16783,"tag":"strategy2","solution":"kkbkkbkkbkkbkkbkbkkkkkbkkkkkbddddakkkkkbkbkpkpdddbkakkkkkbkkabpppaalpaapkkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkei!","problemId":2},{"seed":16783,"tag":"strategy2.500M","solution":"kkbkkbkkbkkbkkbkbkkkkkbkkkkkbddddakkkkkbkbkpkpdddbkakkkkkbkkabpppaalpaapkkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkei!","problemId":2},{"seed":23027,"tag":"strategy2","solution":"kkbkkbkkbkkbkkbkbkkbkkakkpkkpkkpkkppaalpaakkbdddppaalpaapabbbdakkkkbdbdkladdlkei!","problemId":2},{"seed":23027,"tag":"strategy2.500M","solution":"kkbkkbkkbkkbkkbkbkkbkkakkpkkpkkpkkppaalpaakkbdddppaalpaapabbbdakkkkbdbdkladdlkei!","problemId":2},{"seed":23862,"tag":"strategy2","solution":"kkbkkbkkbkkbkkbkbkkkkkbbdpkpdpkpdpklkkkkkbkkkkkbkkkkkbkadpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkakkkkkbdbkkbdakbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbei!kl","problemId":2},{"seed":23862,"tag":"strategy2.500M","solution":"kkbkkbkkbkkbkkbkbkkkkkbbdpkpdpkpdpklkkkkkbkkkkkbkkkkkbkadpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkakkkkkbdbkkbdakbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!l","problemId":2},{"seed":25221,"tag":"strategy2","solution":"kkbkkbkkbkkbkkbkbdbkbkkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkplkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbl","problemId":2},{"seed":25221,"tag":"strategy2.500M","solution":"kkbkkbkkbkkbkkbkbdbkbkkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkplkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbl","problemId":2},{"seed":29639,"tag":"strategy2","solution":"kkbkkbkkbkkbkkbkbkkkbbkddddbkkakkkkkpkkkkkpkkkkkpkpaalpaakpaalpaakkpkkpkpaalpaakpkkbkkbdlkkkddpppkppkpkdpppkpkkpkkpakei!","problemId":2},{"seed":29639,"tag":"strategy2.500M","solution":"kkbkkbkkbkkbkkbkbkkkbbkddddbkkakkkkkpkkkkkpkkkkkpkpaalpaakpaalpaakkpkkpkpaalpaakpkkbkkbdlkkkddpppkppkpkdpppkpkkpkkpakei!","problemId":2},{"seed":679,"tag":"strategy2","solution":"kkbkkbkkbkkbkkbkbdbkbei!kkpkkpkkpkkppaalpaakkkpaalpaakkpaalpaakkkblppppdpkpdlkbdddbkbdbbbei!pppkpdaei!","problemId":2},{"seed":679,"tag":"strategy2.500M","solution":"kkbkkbkkbkkbkkbkbdbkbei!kkpkkpkkpkkppaalpaakkkpaalpaakkpaalpaakkkblppppdppkei!lkbei!kbkei!","problemId":2}] +[{"seed":0,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomicon r'lyehpkakpakaaalyuggothei!kei!","problemId":2},{"seed":13639,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootejohn bigbootenecronomiconnecronomiconph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconia! ia!dei!pdlkabei!ldbldlbkei!kdbbldddbkkkbddbkei!dddei!lei!","problemId":2},{"seed":13948,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!necronomiconnecronomiconnecronomiconnecronomiconia! ia!ayuggoth r'lyehpkkkpkklblblddbkkei!kei!l","problemId":2},{"seed":15385,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootejohn bigbootejohn bigbootejohn bigbootenecronomiconph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn. r'lyehei!ia! ia! r'lyehyuggothia! ia! r'lyehpdia! ia!ia! ia!ia! ia!aadpkia! ia!padddpapakpkei!dddbkkei!","problemId":2},{"seed":16783,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!john bigbootenecronomiconnecronomiconyogsothothia! ia!aadaaaa r'lyehyuggothkpkkei!kei!kei!","problemId":2},{"seed":23027,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!john bigbooteyuggothei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootejohn bigbootenecronomiconia! ia!ia! ia!dei!ppadpkaapalkjohn bigbootedaei!kkakkei!kpdpdpaei!","problemId":2},{"seed":23862,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!necronomicon r'lyehia! ia! r'lyehpia! ia!aakakdpkkkkei!ppaapaakei!lalei!labdei!l","problemId":2},{"seed":25221,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothei!necronomiconyogsothoth r'lyehyuggothei!akia! ia!alei!labdbdblbkkkkkei!lei!dei!l","problemId":2},{"seed":29639,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.yuggothei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconia! ia! r'lyehpia! ia!ayogsothothkkkkei!ia! ia!ayuggothkyuggothkkei!p","problemId":2},{"seed":679,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyuggothph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconnecronomiconjohn bigbootejohn bigbootejohn bigbooteia! ia!john bigbooteapia! ia! r'lyehia! ia!akei!","problemId":2}] diff --git a/submitted/20.json b/submitted/20.json index 83dac0c..6a2c275 100644 --- a/submitted/20.json +++ b/submitted/20.json @@ -1 +1 @@ -[{"seed":0,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconyogsothothlyuggothklalia! ia!adei!l","problemId":20}] +[{"seed":0,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothyuggothia! ia!john bigbooteei!john bigbooteyuggothei!lbddei!aei!abbbkbbbk r'lyehpl","problemId":20}] diff --git a/submitted/24.json b/submitted/24.json index 55638cd..a8b1994 100644 --- a/submitted/24.json +++ b/submitted/24.json @@ -1 +1 @@ -[{"seed":18,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ia! ia!ia! ia!ia! ia!ia! ia!aei!alllabbbakkkbdbbbbkkkpdpkkei!kkia! ia!akei!lbbknecronomiconyogsothothnecronomiconyuggothkei!kyuggothei!aei!d","problemId":24}] +[{"seed":18,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ia! ia!ia! ia! r'lyehei! r'lyeh r'lyehppaap r'lyehbbdei!kppkkei!kkaabyuggothjohn bigbootenecronomiconyogsothoth r'lyehnecronomiconei!aei!l","problemId":24}] diff --git a/submitted/3.json b/submitted/3.json index d6c2743..3fa2e9e 100644 --- a/submitted/3.json +++ b/submitted/3.json @@ -1 +1 @@ -[{"seed":0,"tag":"strategy2","solution":"paalpaapaalpaakpabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkakkkkkpkkkkkakkkkkbkkkkkbkkkkkei!kkkkkbddddbkkkkkakkkkkei!kkkkkbddddakpkkkkkpkkkkkpkkkkkakbkkkkkbkkkkkakkkkkbkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkei!l","problemId":3},{"seed":29060,"tag":"strategy2","solution":"paalpaakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbbdbkbkkkbdakkbdbkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkbdakpddddpkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkbkkkkkbkkkkkbkkkkaddddpkkkkkpkkkkkakkkbkkkkkbkkkkkakkkkbkbabakbkbkbkkkkkakbkkkkkakkkkkakkbkkkkkakkkkkpkkkkkpkkpkkkkkpkpddddbkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbdakei!kkkkkei!kkkkkbdakkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkppdei!l","problemId":3},{"seed":31960,"tag":"strategy2","solution":"paalpaakkkbkdpkkpkkppaalpaaddbkei!kpkpkpabpdllkdppab","problemId":3},{"seed":6094,"tag":"strategy2","solution":"paalpaakkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbbkbkbkbkbkbkbkbkbkbkbbkpaalpaakdbbkkkkkpppddei!kkdpppppaalpaadpkpdpkpdpkpdpkpdpkpdpkpdpkakkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbddakkkkkpkpdpkkpkkkkkpkkkkkpkkkkkpkkkkkpkklkkkkkplklkkkkkplkbkkkkkbkkkkkakkkkkbddakkkkkpkkkkkpklkkkkkplklkkkkkplkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!kkkkkei!kkkkkbddddei!kkkkkei!kkkkkbddddei!kkkkkei!l","problemId":3},{"seed":6876,"tag":"strategy2","solution":"paalpaapaalpaapaalpaakkbkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkakkkkkbkkkkkakkkkkbkakkkkkakkkkkbkkakkkkkakkkkkbkkakkkkkakkkkkbkkakkkkkakkkkkbkkakkkkkpkkkkakkkkkbkkkkkakkkkkbkkkkkakkkkkbkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpdddplkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkaddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddpdei!","problemId":3}] +[{"seed":0,"tag":"strategy2b","solution":"john bigbooteei!ia! ia!aakkakaaakkkkkppppddbkbddddei!dpkkei!","problemId":3},{"seed":29060,"tag":"strategy2b","solution":"necronomicon r'lyehpabbbbdblllkkl r'lyehpkbkei!kei!","problemId":3},{"seed":31960,"tag":"strategy2b","solution":"necronomiconia! ia! r'lyehpabbbbdblllkkl r'lyehpkbkei!kei!","problemId":3},{"seed":6094,"tag":"strategy2b","solution":"john bigbootelei!ia! ia!ei!kpkkpabdppppkpia! ia!pppppda r'lyehpdpkppppaabdpkpdpkpdpkpapaaklkkpdpkpdpkaalei!lyuggothyogsothothl","problemId":3},{"seed":6876,"tag":"strategy2b","solution":"john bigbooteei!a r'lyehplkpaklkkpdpkia! ia!adbkbdlldlia! ia! r'lyeh","problemId":3}] diff --git a/submitted/4.json b/submitted/4.json index bca873c..2502e45 100644 --- a/submitted/4.json +++ b/submitted/4.json @@ -1 +1 @@ -[{"seed":0,"tag":"strategy2","solution":"paalpaapaalpaaddbkkkkppabbbbei!kbakkbkkkkkei!kkkkkpkaddbkkbkkkkkakkkkkpkkkkkpkkpdddbdakkkkkbkkkkkbkkkkkbkkkkkbdakei!kkkkkei!kkkkkbdakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkpldbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkei!ddddpkkkkpddddpkkkkpddddpkkpkei!","problemId":4},{"seed":11006,"tag":"strategy2","solution":"paalpaakbkbkbkbbbei!aalpaabldddldplkei!l","problemId":4},{"seed":12140,"tag":"strategy2","solution":"paalpaaddabbbaddbkkakkkkkbddddakkkkkpkkkkkpkkpabkbkkkkkbkkkkkakkkkkbkkkkkbkaddddpkkkkkpkkkkkpkkkkkpkkkpddddei!kkkkkbddddbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbddddakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkaddddbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkakkkkkbkaddddpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpklddbkkkbdddbkkkbdddbkkkbei!l","problemId":4},{"seed":12272,"tag":"strategy2","solution":"paalpaabbbkppkkkkkkakkkaddlkbkkkkkakbkkkkkbkkkkkbkkkkkakkkkkbkakkkkkei!kkkkkei!kkkkkbddddei!kkkkkei!kkkkkbddddei!kkkkkei!kkkkkbddddei!kkkkkei!kkkkkei!l","problemId":4},{"seed":12352,"tag":"strategy2","solution":"paalpaabbbkpppaei!kpadbkkbkkkkkbkkkkkbdddei!kkkkkbddddbkkkakkkkkbkkkkkbdakei!kkkkkei!kkkkkbdakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkpldbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkbkadddpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkabdddbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!ddddpkkkkpddddpkkkkpddddpkkpkei!","problemId":4},{"seed":12976,"tag":"strategy2","solution":"paalpaabbbkpppkkkkkkei!kkkkkbddddbkkkkkei!kkkkkbddddbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkadbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!kkkkkbddddakkkkkei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpddddpkkkkkei!l","problemId":4},{"seed":13537,"tag":"strategy2","solution":"paalpaaddddpaalpaabdbkbdddlpbbbabdbalkbbbbddbei!pab","problemId":4},{"seed":13661,"tag":"strategy2","solution":"paalpaaddddbkkkkbkpkpkpkplkbkbkbkbakbkbkbkbkakpkpkpkakbkbkbkbkakei!kei!kbei!kei!kbei!kei!kbei!l","problemId":4},{"seed":13694,"tag":"strategy2","solution":"paalpaakbkbkbkbbei!kbbkppddddbkklakbkppplddbkllllkbdakbkkkkkbkkbkkkkakkkkkbkaddddpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpklddddbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkaddddpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpklddddbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkaddddpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpklddbkkkbdddbkkkbdddbkkkbei!l","problemId":4},{"seed":15766,"tag":"strategy2","solution":"paalpaapaalpaadbkkkbkkkkkbkkkkkbbkbkakakei!kpppablei!abl","problemId":4},{"seed":16520,"tag":"strategy2","solution":"paalpaakbkbkbkbbei!kbbddddpkkppabddddei!kkkkkei!ddpdbabbadbkaddbkkkkkbakkkbabdblkpldbadei!akkbbadbbakkkbaei!bei!","problemId":4},{"seed":16868,"tag":"strategy2","solution":"paalpaaddddpaalpaabbbbkbdbdbddpabkkkkkadddddddblllkbkkkkkakkkpbkblkbdlklkbbabbakkdbkkkkei!l","problemId":4},{"seed":17014,"tag":"strategy2","solution":"paalpaakkkkkbkkkkkbkkkkkbkkkkkbbddddbkkkkbkpkpkpppddbakei!kbkkbkkkkakkkkkbkkkkkbkkkkkbkkkakkkkkpkkkkkpkkkkkpkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbdakkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbdakkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbdakkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbdakkpddddpkkkkpddddpkkkkpddddppkei!l","problemId":4},{"seed":177,"tag":"strategy2","solution":"paalpaapaalpaakkpabkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpklkkkkkbkkkkkbkkkkkbkkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpddddpkkkkkei!l","problemId":4},{"seed":17818,"tag":"strategy2","solution":"paalpaabbbbkddddbkkbkpkkkkkpkkkkkpkkkkkpklkkkkkbkkkkkbkkkkkbddaddlklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkplkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbddakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkei!kkkkkei!kkkkkei!l","problemId":4},{"seed":18451,"tag":"strategy2","solution":"paalpaabbkppplkbddddbkkkbdakkkkkbkkkakkbkkkkkbkkkkkbddddbkkei!kkkkkei!kkkkkbdakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkpddddakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkei!kkkkkei!kkkkkbdakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkpldbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkei!ddddpkkkkpddddpkkkkpddddpkkpkei!","problemId":4},{"seed":19530,"tag":"strategy2","solution":"paalpaakkkkkbkkkkkbkkkkkbkkkkkbbddddbkkkkabppplkkkkkbkkkkkei!kkpdppplkklei!pkkl","problemId":4},{"seed":19542,"tag":"strategy2","solution":"paalpaabbkppplkbddddbkkkbdakkkkkbkkbkbdbkkei!kkkkkpddddpkkkkkpkpdlkbkkkkkbkkkkkbkkkkkbkkkkkbdakei!kkkkkei!kkkkkbdakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkpldbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkbkadddpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkabdddbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!ddddpkkkkpddddpkkkkpddddpkkpkei!","problemId":4},{"seed":19957,"tag":"strategy2","solution":"paalpaapaalpaapppabddddbkkkkbkbakkkkkbdakkkkkbakkkkkbkkkkkbkkkkkbbkkkkkplkbkkklbbbkpddbaklblddbkkkbkkplkkkpkkbbkkakkkkkei!kkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkei!kkkkkbddddakkkkkbkkkkkei!dei!","problemId":4},{"seed":20701,"tag":"strategy2","solution":"paalpaakkkkkbkkkkkbkkkkkbkkkkkbbddddbkbpppkpapdlblddbkkkbkkkkkbkkkkkbkkkkkakkkkkbkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkpddddbkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbdddei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkei!kkkkkbddei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkabkkbddddbkkkkbddddbkkkkbdddei!l","problemId":4},{"seed":2148,"tag":"strategy2","solution":"paalpaakkkkkbkkkkkbkkkkkbkkkkkbbkkkkkbkkkkkbkpppabaakbkbkkbdbkbdakkkpddddbbkakpkkkkkpkkkkkpkkkkkpddddpkkakbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkakpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkapkkkkkbdakkkkkpabkkkkkpddddpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkpkkkbddbkkkkkbbbbbkkkkkbddakpppppppddbkbddbkkbddbkkei!pppppdei!l","problemId":4},{"seed":21695,"tag":"strategy2","solution":"paalpaabbbbkddddbkkkei!aalpaakkpkkkkkpkkkkkppdei!","problemId":4},{"seed":21791,"tag":"strategy2","solution":"paalpaapaalpaabbbbkdbdakbkkkkkbkkakkkkkbbddbaklddakkkkbkkkkakkkkkbkei!kkkkkbddddbddddei!kkkkkbei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkei!kkkkkbddddakkkbdddddpkpkkkkpdddddpkkkkkpkkkkkpkabbbbbbbdpppppppddbkbddbkkbddbkei!aei!","problemId":4},{"seed":22290,"tag":"strategy2","solution":"paalpaaddddbkkkkbkpaalpaaddlkbkkkpppplbabbbbblbppplkbddpaplkkkkei!","problemId":4},{"seed":22345,"tag":"strategy2","solution":"paalpaakbkbkbkbbddddbkkkkabpppddddbkaddddlblkppplkbei!pkei!l","problemId":4},{"seed":22572,"tag":"strategy2","solution":"paalpaabbbbkpaalpaaddbkkkkpdbbadbkei!ddbkbddpddakbkkkkkakkkkkpkkkkkpkkpdddbdakkkkkbkkkkkbkkkkkbkkkkkei!kkkkkbddei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkei!kkkkkbddddakkkkkbkkkkkei!ppdpkppab","problemId":4},{"seed":23008,"tag":"strategy2","solution":"paalpaaddddbkkkkbkddddbkakpppplkkkkkbkkkkkei!kkkkpkei!","problemId":4},{"seed":23344,"tag":"strategy2","solution":"paalpaakkkkkbkkkkkbkkkkkbkkkkkbbddddbkkkkakkkakpkkkkkpkkkkkpkkkkkpklkei!","problemId":4},{"seed":23414,"tag":"strategy2","solution":"paalpaabbbbkpaalpaadblbdabkkkkkakkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkadbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkakkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkpkei!l","problemId":4},{"seed":2584,"tag":"strategy2","solution":"paalpaabbbkkkkkkpkkkkkpkkpaalpaakdbdddbkkaldkkkkkpkkkkkpdkkkei!","problemId":4},{"seed":2586,"tag":"strategy2","solution":"paalpaadpaalpaabbbkldbkldddbbkklbdalabkbbkakkkkkbkkkkkakkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkakkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpddddpkkkkkei!l","problemId":4},{"seed":26137,"tag":"strategy2","solution":"paalpaakkkkkbkkkkkbkkkkkbkkkkkbbkkkkkbkkkkkbkkpkpkpkppddpabkpkkkkaddlkkkkkbkbdbkkakkkkkbkkkkkbddakkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbddakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkei!kkkkkei!kkkkkbddddei!kkkkkei!kkkkkei!l","problemId":4},{"seed":26153,"tag":"strategy2","solution":"paalpaabbbbkddddbkkkei!aalpaakkpkkkkkpkkkkpkei!kei!","problemId":4},{"seed":26930,"tag":"strategy2","solution":"paalpaaddddbkkkkbddddbkkkbddddbkkbpddddbkaddddpkpkei!","problemId":4},{"seed":28635,"tag":"strategy2","solution":"paalpaapaalpaadbkkkkpbei!kpkkkkkpkkkkpkei!","problemId":4},{"seed":28921,"tag":"strategy2","solution":"paalpaapaalpaakpabkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpklkkkkkbkkkkkbkkkkkbkkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkbddddakkkkkei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpddddpkkkkkei!l","problemId":4},{"seed":2895,"tag":"strategy2","solution":"paalpaaddddbkkkkbkkkpkkkkkpkkkkkpppkakbkbakbkbkbkbkakpkpkpkakbkbkbkbkakei!kei!kbei!kei!kbei!kei!kbei!l","problemId":4},{"seed":29697,"tag":"strategy2","solution":"paalpaakkkkkbkkkkkbkkkkkbkkkkkbbddddbkkkkakkkapppddpdkpkkkkpkei!aei!l","problemId":4},{"seed":29707,"tag":"strategy2","solution":"paalpaaddddbkkkkbddddbdpppkkplkbkei!kbbkei!kbbkakbkakei!kei!kbei!kei!kbei!kei!kbei!l","problemId":4},{"seed":29971,"tag":"strategy2","solution":"paalpaaddddbkkkkbkpkpkppddlkpklkbkbkkkkbddddbkkkkakkkkkbkkkkkakkkkkbkakkkkkbddakkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkakpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkakpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkaddpkkpddddpkkkkpddddpkkkkpddddppkei!","problemId":4},{"seed":30014,"tag":"strategy2","solution":"paalpaapaalpaabbbei!kei!kbkkkkbkkkkkbdakpkkkkkpkkkkakkkkkbkkkkkbkkkkkbdakpkkkkkpkkkkkakkkkkbkkkkkbkkkkkakkkkkbdddakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkadbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkbkadddpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkldddbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!ddddpkkkkpddddpkkkkpddddpkkpkei!","problemId":4},{"seed":31051,"tag":"strategy2","solution":"paalpaabbbkppkkei!kbbkbkakbkbkakei!kei!kbei!kei!kbei!kei!kbei!kei!kbei!l","problemId":4},{"seed":32001,"tag":"strategy2","solution":"paalpaakbkbkbkbbddddpaalpaabbklbbadddbakkkkkpddddakkkkbkkkkkbkkkkkbkkkkkbdakei!kkkkkei!kkkkkbdakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkpldbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkbkadddpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkabdddbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!ddddpkkkkpddddpkkkkpddddpkkpkei!","problemId":4},{"seed":6045,"tag":"strategy2","solution":"paalpaabbbkkkkkkpkkkkkpkkkkkpkkkpdddbkkakkkkpkkbakbkbkdbdlakei!ddabkkkkkei!","problemId":4},{"seed":6532,"tag":"strategy2","solution":"paalpaakbkbkbkbbddddpaalpaadbdbkadakkbdbablldei!dei!kkkei!kkkkkbddddbkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkakkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpdlkklkkbbbbbbbdpdpdpkpdppkei!ablblei!","problemId":4},{"seed":7533,"tag":"strategy2","solution":"paalpaaddddbkkkkbkpkpkppakkkkkbdakkkkkei!dbddddbkkkkkbkkkkkbkkkkkbbakkkkkbdakkkkkei!dbddddbkkkkkbkkkkkakkkkkpkkkkkakkkkkbkkkkkbkkkkkei!kkkkkbddddbkkkkkakkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkabkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkei!kkkkkbddddakkkkkei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkpkei!l","problemId":4},{"seed":8269,"tag":"strategy2","solution":"paalpaakkkkkbkkkkkbkkkkkbkkkkkbbei!kbbddddpaalpaakdbdbkadlkkbbbakkklkpppabpabbbei!l","problemId":4},{"seed":8444,"tag":"strategy2","solution":"paalpaabbbkddddbkkkakkkkkbkkkkkbkkakkkkkbkkkkkbkkkakkkkkbkkkkkakkkkkbkakkkkkbddakkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkakpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkakpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkaddpkkpddddpkkkkpddddpkkkkpddddppkei!","problemId":4},{"seed":8466,"tag":"strategy2","solution":"paalpaapaalpaabbbei!kei!kbkkkkbkkkkkbdakpkkkkkpkkkkkakkkkkbkkkkkbkkkkkakkkkkbdddakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkpddddakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkakkkkkbkadddpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkldddbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkadddpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkldddbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!ddddpkkkkpddddpkkkkpddddpkkpkei!","problemId":4},{"seed":8700,"tag":"strategy2","solution":"paalpaaddddpaalpaabbbbkdbdlkkkkbkkkkdlldadbkkkkkbkbkdldldakei!kkpaddddbkkkkkbkkkkkakkkkkbkkkkkbkkkkkbkkkakkkkkei!kkkkkbddddakkkkkbkkkkkei!kkkkkbddei!kkkkkpkkkkkpkkkkpdddddpkkkkkpkkkkkpkabbbbbbbdpppppppddbkbddbkkbddbkei!aei!","problemId":4}] +[{"seed":0,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteia! ia!necronomiconyogsothothyuggothei!john bigbootenecronomiconei!pdia! ia!paa r'lyehppakei!kei!lei!","problemId":4},{"seed":11006,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothia! ia!necronomiconei!ab r'lyehpaallallei!ldei!","problemId":4},{"seed":12140,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconbpia! ia!aalbdallkkkei!lei!","problemId":4},{"seed":12272,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia! r'lyehyuggothei!ia! ia! r'lyehpbdbllei!ppkbbbbkbdei!","problemId":4},{"seed":12352,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothyuggothia! ia!ei! r'lyehei!apkia! ia!akaadbbei!paddei!lei!l","problemId":4},{"seed":12976,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!ia! ia!lei!aadbbyogsothoth","problemId":4},{"seed":13537,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothyuggothnecronomiconia! ia!necronomiconei!necronomiconpia! ia!kapa r'lyehyuggothkbblblkkei!lei!","problemId":4},{"seed":13661,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothyuggothia! ia!ia! ia!klbbllei!dbei!","problemId":4},{"seed":13694,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteia! ia!necronomiconyogsothothyuggothei!john bigbooteyogsothothia! ia!ia! ia!lpkei!kkakpppdpkpaei!","problemId":4},{"seed":15766,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothyuggothei!dei!ppkblyuggoth","problemId":4},{"seed":16520,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothyuggothia! ia!ei!necronomiconpadbbbei!appaei!pkadabbbbdei!kkkkkbddddbdei!a","problemId":4},{"seed":16868,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!john bigbooteei!john bigbooteyuggothyogsothothnecronomiconei!adabkkkpppdbbbkei!bbkkl","problemId":4},{"seed":17014,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!ia! ia!ei!kpablbbddadbdbkblbdlalaei!lei!ayuggothbkkei!kbei!","problemId":4},{"seed":177,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia! r'lyehei!ia! ia!kablbyuggothkabbkbei!ppkdbkkei!","problemId":4},{"seed":17818,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!john bigbootedbei!apppkalalei!lei!lei!lei!dpkpddlkppaei!l","problemId":4},{"seed":18451,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!dlbei!bblei!kpkpddei!kei!","problemId":4},{"seed":19530,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconei!ia! ia!akappia! ia!bbbei!ppdei!","problemId":4},{"seed":19542,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!necronomiconei!kia! ia!kkapllbei!bbei!","problemId":4},{"seed":19957,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteia! ia!necronomiconyogsothothei!ia! ia!john bigbooteyuggothia! ia!ia! ia!lppkei!kkei!ppkbbei!","problemId":4},{"seed":20701,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconbblei!kia! ia!pkaalayuggoth","problemId":4},{"seed":2148,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconbei!aanecronomiconakpk r'lyeh","problemId":4},{"seed":21695,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconei!akia! ia!kapa r'lyehei!akkkei!kppddddei!","problemId":4},{"seed":21791,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!john bigbooteei!john bigbooteyuggothia! ia!kkia! ia!aabbdlbkei!blbei!dpkpakldpppkakl","problemId":4},{"seed":22290,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteia! ia!necronomiconyuggothyogsothothei!necronomiconei!kei!akbkei!kpia! ia!akapkkbkpkbdpkpkkkkpkei!l","problemId":4},{"seed":22345,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!john bigbooteyuggothei!aei!akkkei!l","problemId":4},{"seed":22572,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!ia! ia!ia! ia!apdbdbei!dbddddei!l","problemId":4},{"seed":23008,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!john bigbooteyuggothei!john bigbooteyuggothei!bbei!aadppkpkkei!","problemId":4},{"seed":23344,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!john bigbooteei!ia! ia! r'lyehei! r'lyehpkbbei!lbkbddei!lkei!","problemId":4},{"seed":23414,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothia! ia!necronomiconei!john bigbooteia! ia!ia! ia!pkadlbldyogsothothdlblei!dblkbdei!bbbblkbei!","problemId":4},{"seed":2584,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!necronomiconei!ia! ia!ia! ia!ayuggothla r'lyehyuggothlkbbei!paaei!kpkpkkkkkbdei!kkkkpkei!","problemId":4},{"seed":2586,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!ei! r'lyehjohn bigbooteia! ia!ia! ia!bblei!lkpakblbei!kpp r'lyeh","problemId":4},{"seed":26137,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!john bigbooteei!aei!pkaddbkbbdpdaadlkbbbei!kei!l","problemId":4},{"seed":26153,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconei!akia! ia!kaplbblblkdbkbdbdei!l","problemId":4},{"seed":26930,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteei!akia! ia!alei!akallalaaei!kei!","problemId":4},{"seed":28635,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconkapia! ia!ei!abdbblblkbbei!pppaei!dllaei!dbblei!ppkaakllyogsothothyuggothl","problemId":4},{"seed":28921,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!john bigbooteei!ia! ia!ia! ia!necronomiconbei!aapakpp r'lyeh","problemId":4},{"seed":2895,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconyuggothkbldlei!bbei!","problemId":4},{"seed":29697,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!ayuggothei!apakei!lei!lklaldyuggoth","problemId":4},{"seed":29707,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconei!aei!abei!","problemId":4},{"seed":29971,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ia! ia!aklb r'lyehppkpakblabbbei!ppkl","problemId":4},{"seed":30014,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothyuggothei!dpdpkaaayuggothlalkkkkkei!kkkkkei!","problemId":4},{"seed":31051,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!necronomiconei!pd r'lyehbei!dpkaaadpdpkkpkkkpkei!","problemId":4},{"seed":32001,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteia! ia!necronomiconyogsothothyuggothei!necronomiconkaadlbbei!bbei!paakei!lalkei!dbei!alkaei!","problemId":4},{"seed":6045,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ei!ia! ia!kadlei!dblbllkbbei!bbei!","problemId":4},{"seed":6532,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!ia! ia!ia! ia!lbbdllkbbei!pkpkkkpkei!kei!","problemId":4},{"seed":7533,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconyuggothia! ia!john bigbooteei!klkakpkklbbei!bbei!l","problemId":4},{"seed":8269,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothyuggothia! ia!necronomiconbppaayuggothei!papkei!addbkbkaei!","problemId":4},{"seed":8444,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconia! ia!john bigbooteyogsothothei!abei!","problemId":4},{"seed":8466,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconyogsothothia! ia!ei!ia! ia!ia! ia!kanecronomiconyuggothei!lbbei!bbei!","problemId":4},{"seed":8700,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconia! ia!ia! ia!john bigbooteei!necronomiconapaaei!abkppaakbpddddpdbbei!ei!","problemId":4}] diff --git a/submitted/5.json b/submitted/5.json index 9db6e78..7bbd524 100644 --- a/submitted/5.json +++ b/submitted/5.json @@ -1 +1 @@ -[{"seed":0,"tag":"strategy2","solution":"bkadpaalpaadpaalpaadbdakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkapkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!pppkpdpdei!","problemId":5},{"seed":11460,"tag":"strategy2","solution":"kakbkbkbkbkbkbkbkbkbkbkbkbkbkbkei!kei!kbei!kei!kbei!kei!kbei!kei!kbei!kei!kbei!kei!kbei!kei!kbei!kei!l","problemId":5},{"seed":14027,"tag":"strategy2","solution":"bbbbkpaalpaadbkakpddpabdei!kkkkkbdddbklaklkpaalpaakbakkalpkllei!","problemId":5},{"seed":15215,"tag":"strategy2","solution":"bbbkkpaalpaapaalpaakkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpdabkkkbkkkkkbkkkkkbkkkkkbkkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpdplkbdbkkkbkkkkkbkkkkkakkkkkbkkkkkakkkkkbkakkkkkpkkkkklkkkkkbkkkakkkkkpkkkkkakkkkkbkkkkkakkkkkbkkkkkakkkkkbddei!kkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddppkei!","problemId":5},{"seed":15577,"tag":"strategy2","solution":"bkdpaalpaakkklpadpkpkbdbbbkkkbdddbkkkbdddbkkkbdddbkkkbdddbkkkbdddbkkkakkkkkbddddakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkbkkkkkbddddbkkkkkbkkkkkbkkkkkbkkkkkbkkkkakkkkkbkaddddpkkkkkpkkkkkpkkkkkpkkkkpdlkbkkkkkbkkkkkbkkkkkbkkkkkbkaddddpkkkkkpkkkkkpkkkkadbkbkkkkkbkkkkkbkkkkaddddpkkkkkpkkplbddddbkkkkkbkkaddddpkpdabkbkkkkkbkkkkaddddpkkkkkpkpdpdpkkpdpdakbkkkkkbkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkakkkkkbdddakkpdddpkkkpdddpkkkpdddpkkkpdddpkkkpdddpkkkpdddpkkkpdddpkkkpdddpkkkpdddpkkkpdddpkkkpdddpkkkpdddpkkkpddpkpddbei!l","problemId":5},{"seed":22837,"tag":"strategy2","solution":"bbbkpaalpaakpkpkpkpkpkpkpkpkpkpkpkpkpkplkbkbkbkbkbkbkbkbkbkbkbkbkbkbkbkbkbkbkbkbkbkbkbkbkbkbkbkakbkakei!kei!kbei!kei!kbei!kei!kbei!kei!kbei!kei!kbei!kei!kbei!kei!l","problemId":5},{"seed":24851,"tag":"strategy2","solution":"bbbkkkbkakkkkkbkbkkkkkbkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkei!kkkkkei!kkkkkbdakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpddlkbkkkkkbkkkkkbkkkkkbkkkkkbkei!kkkkkei!kkkkkbdakkkkkpkkkkkpkkkpdlbkbkkkkkbkkkei!kkkkkei!kkkkkbdakkkkkpkkkkkpkkakkkkkbkkkkkbkkkkkbdddakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbdddakkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkpddddpkkkkppdei!l","problemId":5},{"seed":32620,"tag":"strategy2","solution":"bbbkpaalpaadei!paalpaapklbdbkbddbkkkbdddbkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkakkkkkbkadddpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpddddakkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkadddpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbdddakkkpkkkkkpkkkkkpkkkkkpkkkkkpkaddbkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbdddakkkkkpkkkkkpkkklddddbkkkkkbkakkkkkbkadddpkkkkkpkaddddbkkkkkbkkkkkbkkkadddpkkkkkpkkkkkpkkkkkpkkpkkkkkpkkkkkpkkpkkkkkpkpddddbkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpddpkldbkkbkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddakpddpkkpddpkkpddpkkpddpkkpddpkkpddpkkpddpkkpddpkkpddpkkpddpkkpddpkkpddpkkpddppkei!l","problemId":5},{"seed":32719,"tag":"strategy2","solution":"bkddpkpkpddei!kkkbddbkbdddpkakkkkkbkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkakkkkkbkadddpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbdddakkkpkkkkkpkkkkkpkkkkkpkkkkkpkaddbkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbdddakkkkkpkkkkkpkkklddddbkkkkkbkakkkkkbkadddpkkkkkpkaddddbkkkkkbkkkkkbkkkadddpkkkkkpkkkkkpkkkkkpkkpkkkkkpkkkkkpkkpkkkkkpkpddddbkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpddpkldbkkbkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddddbkkkkbddakpddpkkpddpkkpddpkkpddpkkpddpkkpddpkkpddpkkpddpkkpddpkkpddpkkpddpkkpddpkkpddppkei!l","problemId":5}] +[{"seed":0,"tag":"strategy2b","solution":"necronomiconjohn bigbooteyogsothothyuggothia! ia! r'lyehei!necronomiconyogsothothkei!kklei!akpia! ia!kkei!kpdpkaaadpkkpkkkkkpdpkpdpkpaklalalalayuggothkkei!l","problemId":5},{"seed":11460,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.kkkei!adpaei!ppakpaaalakpkalayuggothyogsothoth","problemId":5},{"seed":14027,"tag":"strategy2b","solution":"necronomiconph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothei! r'lyehei!adpadei!akkkkkappkaadppkpkkkkkpppppkaalalalalalei!lkkkkkei!","problemId":5},{"seed":15215,"tag":"strategy2b","solution":"john bigbootenecronomiconyogsothoth r'lyehei!ia! ia!ddia! ia!ia! ia!kdapakpppaei!dpdpkppkaaapkallljohn bigbooteei!l","problemId":5},{"seed":15577,"tag":"strategy2b","solution":"john bigbootenecronomiconyogsothothia! ia!yuggoth r'lyehei!ia! ia!ei! r'lyehei!ppdia! ia!pppdaaei!klkkkei!","problemId":5},{"seed":22837,"tag":"strategy2b","solution":"necronomiconjohn bigbooteyogsothothia! ia!yuggoth r'lyehei!ia! ia!akpaldbei!dbblbei!akkbkbdbbbnecronomiconlyogsothoth r'lyehpdei!l","problemId":5},{"seed":24851,"tag":"strategy2b","solution":"john bigbootenecronomiconyogsothothyuggothia! ia!a r'lyehei!necronomiconia! ia!kbdbbdlei!bdbbbdllldadbbbdnecronomiconia! ia!kkei!l","problemId":5},{"seed":32620,"tag":"strategy2b","solution":"john bigbootenecronomiconyogsothothia! ia! r'lyehei!john bigbooteei!apaklaaddddpppabddpkpddkkkbdbbdlllakbbbbdnecronomiconia! ia!kkei!l","problemId":5},{"seed":32719,"tag":"strategy2b","solution":"necronomiconjohn bigbooteyogsothothia! ia!yuggothei!kkei!kbei!ldei!","problemId":5}] diff --git a/submitted/6.json b/submitted/6.json index 81580d7..663e159 100644 --- a/submitted/6.json +++ b/submitted/6.json @@ -1 +1 @@ -[{"seed":0,"tag":"lilik0b","solution":"iiiiiiiimmiiiiiimimmiiiimimimmimimimimmimimimeemimeeeemimimimimiiiiiimmeemimimimimiimimimmeemimimimmeeeemimimimmiiiiiipmiimimimeeemmimimmemimimimiiiiiimeeemimimimimeeemimimimmiiiimemimimmiiiipimeeemimimmiiiippmeeeeemimimimiiiimmimimeemimimeeeemimimiiiipmeeemmimmiimimmmimimeemimimimmeeemimiiiiipmiiiimmeeemimimiiiipmmiipmmimmiippimemimeeeemimmiipppmeeeeemimimmiimipmeeeemimimiimmeeeeemimmeemimmeeeemimiiippmiippmiiimmiimimmmmmeeeemimmiippimmimimeemimimimmeemimimimmeemimimimiimimimeeemmimimmmiiiiipimeemimimimmiiiimimmiiiiiiiimiimimimimeeemmimimimmiiiiiimimmemimimimimmimimimeemimiiiiiiiimiiiimimimiimimimmimmimimimimmeeeemimimimimmmimimimimeemimimimimmmemimimmiiiiiiimiimimimmiiiiiimeeeeemimimimimmimimimmmmemimimmeeeemimimimmiimimimmiiiiiipmeeeeemimimimimmiiiiimmemimimimimmmmimimmeeeemimimimimeeemimimimmiimimimeeemmimimmiiiiiiimimiiiiiimimmiiiiiiiimmimimimimiiiimimimeemimimimimmeeemimimimimiiiiiiimiiiimimmemimimimmeemimimimeeemmimimmiiiiiimmiiiipmmiiimmmimimeemimimeeemmimmiiiippmiiiimiiippimiimimeemimimeeeemimimiiiipmeemimimiimiimimmimeeemimimmippipmmiimemimmipimeeeemimmeemimiippimeeeeemimimmmimmmeeeemimimiiipimmiipmemimmeeeemimimiipipimmipppimeeemimmpppmmpmeeeeemimmemm","problemId":6},{"seed":10919,"tag":"strategy2","solution":"bbbbbbpaalpaapaalpaabbbbbbbbbbkddpaalpaaddbklkbkppababababbbbbldlklkbkei!kkkkkbddddakkkkkbkkkkkakkkkkbddakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkei!l","problemId":6},{"seed":11993,"tag":"strategy2","solution":"bbbbbbpaalpaapaalpaapaalpaakbkddpabppaei!pdldlkkbkkdldlkkbaalabbbbei!pppppppabbbbbbbbei!pppppppabbbbbbbbei!l","problemId":6},{"seed":13120,"tag":"strategy2","solution":"bbbbbbdddpaalpaapaalpaakpabbbbbbkkpppldpdei!","problemId":6},{"seed":13185,"tag":"strategy2","solution":"bbbbbbkbkddpaalpaappplkkbkkbkkakkbkkakkbkkbkkbkkbkkbkkakkpkkpkkpkkpkkpkkpklkkbkkbkkbkkbkkbkkbkkakkpkkpkkpkkpkkpkkpkkpkakbkkbkkbkkbkkbkkbkkbkkbkkakkpkkpkkpkkpkkpkpkei!l","problemId":6},{"seed":13859,"tag":"strategy2","solution":"bbbbbbkbdbdppaalpaapaalpaakkkkkbkkkkkbkkkpaalpaadldakkkaddddbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbddakkkpabkakkkkkbddddakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkklkbkpkpklei!ppab","problemId":6},{"seed":14118,"tag":"strategy2","solution":"bbbbbbpaalpaapaalpaapabkbkbddei!pppabbbpabbbbbei!abbbbbbbldbbbkpppabdpabdddbbbbkkei!","problemId":6},{"seed":1519,"tag":"strategy2","solution":"bbbbbbpaalpaapaalpaakbbbkddpaalpaalkkllkdbddpppkpdldpdei!l","problemId":6},{"seed":15379,"tag":"strategy2","solution":"bbbbbbpaalpaapaalpaapaalpaabdbkkblbbbei!pplbbei!ppppabbbbbei!pppppppplbbbbbbbbei!ppppppppa","problemId":6},{"seed":15671,"tag":"strategy1","solution":"aaaaaaaallaaaaaaallaaaaaallaaaaallaaaalaaalaalall","problemId":6},{"seed":16393,"tag":"strategy1","solution":"aaaaaaaallaaaaaalalaaaaaallaaaaalaaallalalaaaalaaalaalal","problemId":6},{"seed":16650,"tag":"strategy2","solution":"bbbbbbbbbbbdddpaalpaapaalpaapaalpaakbkppkddbdaddpdpppddei!","problemId":6},{"seed":16903,"tag":"strategy1","solution":"aaaaaaaallaaaaaalalaaaaaallaaaaaalaaaaalaaalllaalaaaalaaalallaallllaalllaaallal","problemId":6},{"seed":17013,"tag":"strategy2","solution":"bbbbbbbbbbbpaalpaapaalpaakpaalpaakbklkkkkkbkbdakkkkkbkakkkkkei!kkkkkei!kkkkkbddddei!kkkkkei!kkkkkbddddei!kkkkkei!l","problemId":6},{"seed":17114,"tag":"strategy2","solution":"bbbbbbddpaalpaapaalpaakkkkpabbbkpkakkbkkkkkakplbdppppddpppkpabbbbbei!lei!pppppabbbbbbei!ppppppabbbbbbbei!pppppppabbbbbbbbei!l","problemId":6},{"seed":18093,"tag":"strategy2","solution":"bbbbbbbbbbbddpaalpaapaalpaakpabkkppdddbkadddpkkkkpkei!kei!","problemId":6},{"seed":18588,"tag":"strategy2","solution":"bbbbbbbbbbbpaalpaapaalpaakkpabei!kkpabdlbabbbei!ppppabbbbbei!pppppppabbbbbbbbei!pppppppabbbbbbbbei!l","problemId":6},{"seed":19086,"tag":"strategy2","solution":"bbbbbbkkpppplbbei!pplbbbbbbbbei!pppppppplbbbbbbbbei!pppppppplbbbbbbbbei!ppppppppa","problemId":6},{"seed":21458,"tag":"strategy1","solution":"aaaaaaaallaaaaaaaalaaaaaaalaaaaaalaaaaalaaaalllalaaaallllaaaalllaaaalaaalaalllllalaalal","problemId":6},{"seed":21728,"tag":"strategy2","solution":"bbbbbbbbbbbkkpppplbbei!pplbbbbbbbbei!pppppppplbbbbbbbbei!pppppppplbbbbbbbbei!ppppppppa","problemId":6},{"seed":22079,"tag":"strategy1","solution":"aaaaaaaallaaaaaaaalaaaaaaalaaaaaalllaaaaaalaaaaalaaaallalaaaalllaaaalaaalaalall","problemId":6},{"seed":23220,"tag":"strategy2","solution":"bbbbbbbbbbbkbkpaalpaapaalpaabpppabl","problemId":6},{"seed":23256,"tag":"strategy1","solution":"aaaaaaaallaaaaaalalaaaaaallaaaaallaaaaalaaallllalaaallllaaallaalalllalalllallllalll","problemId":6},{"seed":24334,"tag":"strategy1","solution":"aaaaaaaallaaaaaaaalaaaaaalllaaaaaaalaaaaallaaaallaaaalaaalaalal","problemId":6},{"seed":24513,"tag":"strategy2","solution":"bbbbbbbbbbbkkpppplbbei!pplbbbbbbbbei!pppppppplbbbbbbbbei!pppppppplbbbbbbbbei!ppppppppa","problemId":6},{"seed":24524,"tag":"strategy2","solution":"bbbbbbkbkdddpaalpaapaalpaabpppkpappabbblbbbbbei!pppppabbbbbbei!pppppppplbbbbbbbbei!ppppppppa","problemId":6},{"seed":24732,"tag":"strategy2","solution":"bbbbbbddpaalpaapaalpaakpabbbkblbbbei!ppppabbbbbei!ppppppabbbbbbbei!pppppppplbbbbbbbbei!ppppppppa","problemId":6},{"seed":25267,"tag":"strategy2","solution":"bbbbbbpaalpaapaalpaakpaalpaakbkkbkkkkkbkkkkkbbdbkbkddbkakkkkbkkkddbdadllkkkkbkkddbdadllkkbbalaapabbbbbbei!pppppppplbbbbbbbbei!ppppppppa","problemId":6},{"seed":25460,"tag":"strategy2","solution":"bbbbbbddpaalpaapaalpaakpabkbdei!kkkkkbddddbddakkkkkbkkakkkkkei!kkkkkei!kkkkkbddddei!kkkkkei!kkkkkbddddei!kkkkkei!l","problemId":6},{"seed":25499,"tag":"strategy2","solution":"bbbbbbkkppaalpaapppplbbei!pplbbbbbbbbei!pppppppabbbbbbbbei!pppppppplbbbbbbbbei!ppppppppa","problemId":6},{"seed":25536,"tag":"strategy2","solution":"bbbbbbbbbbbdddpaalpaapaalpaakpaalpaabbbbbei!pppabbbbei!ppppppabbbbbbbei!pppppppplbbbbbbbbei!ppppppppa","problemId":6},{"seed":26670,"tag":"strategy2","solution":"bbbbbbddpaalpaapaalpaakpaalpaakbdbdddbklkpkkkbkbkkldlllkkbkkbkkbdapkkbdakkbkakkpkkpkkpkkpkkpkkpkkpkkalei!pkldl","problemId":6},{"seed":26708,"tag":"strategy2","solution":"bbbbbbkbdbdppaalpaapaalpaakpaalpaapbblbbblbabbbei!pppabbbbei!pppppabbbbbbei!pppppppabbbbbbbbei!l","problemId":6},{"seed":26906,"tag":"strategy2","solution":"bbbbbbpaalpaapaalpaapaalpaabbei!","problemId":6},{"seed":28599,"tag":"strategy2","solution":"bbbbbbbbbbbbbbbkpdpaalpaapaalpaakpabbabbbei!ppppabbbbbei!pppppplbbbbbbei!pppppppplbbbbbbbbei!pppppppplei!pab","problemId":6},{"seed":2860,"tag":"strategy2","solution":"bbbbbbkbkdddpaalpaaddei!kkb","problemId":6},{"seed":29169,"tag":"strategy2","solution":"bbbbbbkbkddpaalpaapaalpaapaalpaappplbbdbdakbkbkbkkbkkbdakkpkkpkkpkkpkkakkbkkbkkbkkbkkakkbkkakkpkkpkkpkkpkkpkkpkkpkakbkkbkkbkkbkkbkkbkkbkkbkkakkpkkpkkpkkpkkpkpkei!l","problemId":6},{"seed":31026,"tag":"strategy2","solution":"bbbbbbkbkddpaalpaapaalpaabbpaalpaapdlkpppakkei!aei!","problemId":6},{"seed":3703,"tag":"strategy2","solution":"bbbbbbpaalpaapaalpaapaalpaadpabbbbbbbbbdbkakkbkkkpablkbdbkakkkkkbddakkkkkpkkkkkpkkkkkpkaddbkkkkkbkkkkkbkkkkkakkkkkbkkkkkakkkkkbddakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpklkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkei!l","problemId":6},{"seed":5343,"tag":"strategy2","solution":"bbbbbbdddpaalpaapaalpaakpaalpaakbdbdppababbbdbkllbbbei!pppabbbbei!pppppppabbbbbbbbei!pppppppabbbbbbbbei!l","problemId":6},{"seed":629,"tag":"strategy2","solution":"bbbbbbbbbbbbbbbbbbei!ppaalpaakkpaalpaapaalpaapaalpaababbbbei!ppabbbei!pppplbbbbei!pppppppplbbbbbbbbei!pppppppplei!","problemId":6},{"seed":6839,"tag":"strategy1","solution":"aaaaaaaallaaaaaaaalaaaaaaalllaaaaaaallaaaaaalaaaaalaaaallalalaaaallallaaaallalaaaalaallallllaallallaalllaaalaalalllallall","problemId":6},{"seed":7082,"tag":"strategy2","solution":"bbbbbbddpaalpaapaalpaakpabbbei!pppabbbbbei!pppplbbbbei!ppppppabbbbbbbei!pppppppabbbbbbbbei!l","problemId":6},{"seed":7610,"tag":"strategy2","solution":"bbbbbbdddpaalpaapaalpaapaalpaadpabkbkldakbbbbllbbei!ppabbbei!pppppppabbbbbbbbei!pppppppabbbbbbbbei!l","problemId":6},{"seed":8123,"tag":"strategy2","solution":"bbbbbbbbbbbkbkpaalpaaei!pppabbbbbbbbei!ppppplbbbbbei!pppppppabbbbbbbbei!pppppppabbbbbbbbei!l","problemId":6},{"seed":8466,"tag":"strategy2","solution":"bbbbbbdddpaalpaapaalpaakpaalpaakbkkbklpdbkbkei!pdei!l","problemId":6},{"seed":8780,"tag":"strategy2","solution":"bbbbbbdddpaalpaapaalpaakpaalpaappabddbkkkapbllbbbbbllbei!pplbbbei!pppppppabbbbbbbbei!pppppppabbbbbbbbei!ab","problemId":6},{"seed":8856,"tag":"strategy2","solution":"bbbbbbdddpaalpaapaalpaakpabkkpppldpdei!","problemId":6},{"seed":9536,"tag":"strategy2","solution":"bbbbbbkkpppplbbei!pplbbbbbbbbei!pppppppplbbbbbbbbei!pppppppplbbbbbbbbei!ppppppppa","problemId":6},{"seed":9816,"tag":"strategy1","solution":"aaaaaaaallaaaaaaallaaaaaaalaaaaaalaaaaalaaaalaaalaalall","problemId":6}] +[{"seed":0,"tag":"lilik0b","solution":"iiiiiiiimmiiiiiimimmiiiimimimmimimimimmimimimeemimeeeemimimimimiiiiiimmeemimimimimiimimimmeemimimimmeeeemimimimmiiiiiipmiimimimeeemmimimmemimimimiiiiiimeeemimimimimeeemimimimmiiiimemimimmiiiipimeeemimimmiiiippmeeeeemimimimiiiimmimimeemimimeeeemimimiiiipmeeemmimmiimimmmimimeemimimimmeeemimiiiiipmiiiimmeeemimimiiiipmmiipmmimmiippimemimeeeemimmiipppmeeeeemimimmiimipmeeeemimimiimmeeeeemimmeemimmeeeemimiiippmiippmiiimmiimimmmmmeeeemimmiippimmimimeemimimimmeemimimimmeemimimimiimimimeeemmimimmmiiiiipimeemimimimmiiiimimmiiiiiiiimiimimimimeeemmimimimmiiiiiimimmemimimimimmimimimeemimiiiiiiiimiiiimimimiimimimmimmimimimimmeeeemimimimimmmimimimimeemimimimimmmemimimmiiiiiiimiimimimmiiiiiimeeeeemimimimimmimimimmmmemimimmeeeemimimimmiimimimmiiiiiipmeeeeemimimimimmiiiiimmemimimimimmmmimimmeeeemimimimimeeemimimimmiimimimeeemmimimmiiiiiiimimiiiiiimimmiiiiiiiimmimimimimiiiimimimeemimimimimmeeemimimimimiiiiiiimiiiimimmemimimimmeemimimimeeemmimimmiiiiiimmiiiipmmiiimmmimimeemimimeeemmimmiiiippmiiiimiiippimiimimeemimimeeeemimimiiiipmeemimimiimiimimmimeeemimimmippipmmiimemimmipimeeeemimmeemimiippimeeeeemimimmmimmmeeeemimimiiipimmiipmemimmeeeemimimiipipimmipppimeeemimmpppmmpmeeeeemimmemm","problemId":6},{"seed":10919,"tag":"strategy2b","solution":"ia! ia!john bigbooteyogsothothnecronomiconei!john bigbooteyuggothph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconnecronomiconia! ia!ia! ia!dlei!blbbkkbei!ppia! ia!ei!kkbkppkei!kkbk r'lyehpl","problemId":6},{"seed":11993,"tag":"strategy2b","solution":"ia! ia!john bigbootenecronomicon r'lyehei!ia! ia!ia! ia!john bigbooteyogsothothnecronomiconjohn bigbootenecronomicondia! ia!ia! ia!ia! ia!aei!dplabddpddei!lblaaaaei!aei!l","problemId":6},{"seed":13120,"tag":"strategy2b","solution":"ia! ia!john bigbootenecronomiconyogsothothyuggothei!john bigboote r'lyehjohn bigbootenecronomiconyogsothothia! ia!john bigbooteia! ia!ia! ia! r'lyehkkbdbbei!lkkbkbei!pkei!","problemId":6},{"seed":13185,"tag":"strategy2b","solution":"ia! ia!john bigbootenecronomiconyogsothoth r'lyehpbbei!pa r'lyehei! r'lyehpkkei!l","problemId":6},{"seed":13859,"tag":"strategy2b","solution":"ia! ia!john bigbooteyogsothothnecronomiconei!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ia! ia!ddbkkbei!kpdpkpkddbkei!ddbdei!ddpdei!","problemId":6},{"seed":14118,"tag":"strategy2b","solution":"ia! ia!john bigbooteyogsothothnecronomiconph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ei!ia! ia!john bigbootenecronomiconnecronomiconddia! ia!akaaakkbkkkei!kaaakei!","problemId":6},{"seed":1519,"tag":"strategy2b","solution":"ia! ia!john bigbootenecronomiconyogsothothyuggothei! r'lyehnecronomiconnecronomicondkei!ia! ia!aaa r'lyehp r'lyeh","problemId":6},{"seed":15379,"tag":"strategy2b","solution":"ia! ia!john bigbootenecronomiconyuggothyogsothothei! r'lyehnecronomiconia! ia!john bigbooteyuggothia! ia!ia! ia!aei!lei!abei!","problemId":6},{"seed":15671,"tag":"strategy2b","solution":"ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteei!necronomiconei!aei!pkei!kei!","problemId":6},{"seed":16393,"tag":"strategy2b","solution":"ia! ia!john bigbooteyogsothothph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconei!pnecronomiconnecronomiconyuggothbbei!bbblei!aei!pbbbbldpdei!dei!l","problemId":6},{"seed":16650,"tag":"strategy2b","solution":"ia! ia!ia! ia!john bigbooteyogsothothnecronomicon r'lyehyuggothei!ia! ia!john bigbooteyuggothnecronomiconei!ia! ia!ia! ia!ia! ia!aei!pkkbdbklllk r'lyehpl","problemId":6},{"seed":16903,"tag":"strategy2b","solution":"ia! ia!john bigbooteyogsothothnecronomiconyuggoth r'lyehei!john bigbootejohn bigbooteyogsothoth r'lyehnecronomiconei!ldppaakei!lalei!kbkbk r'lyeh","problemId":6},{"seed":17013,"tag":"strategy2b","solution":"ia! ia!ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconei!john bigboote r'lyehia! ia!abbei!ppaalei!ppaaaei!ppaakei!pppdddei!","problemId":6},{"seed":17114,"tag":"strategy2b","solution":"ia! ia!john bigbooteyogsothothei!john bigbootenecronomiconph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ia! ia!john bigbootejohn bigbootejohn bigbooteia! ia!ia! ia!alklakkei!ppaaei!ei!pdkei!ppakyuggoth","problemId":6},{"seed":18093,"tag":"strategy2b","solution":"ia! ia!ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconjohn bigbooteyuggothei! r'lyehpklkbnecronomiconaei!ia! ia!ei!apaei!lbei!aaei!a","problemId":6},{"seed":18588,"tag":"strategy2b","solution":"ia! ia!ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconjohn bigbooteei!john bigbooteia! ia!necronomiconia! ia!ia! ia!ia! ia!lei!akei!laaei!aei!","problemId":6},{"seed":19086,"tag":"strategy2b","solution":"ia! ia!john bigboote r'lyehei!john bigbootenecronomiconyogsothothnecronomiconjohn bigbooteei!kei!ia! ia!aia! ia!lei!l","problemId":6},{"seed":21458,"tag":"strategy2b","solution":"ia! ia!john bigbootenecronomicon r'lyehei!john bigbooteyogsothothyuggothnecronomiconia! ia!laap","problemId":6},{"seed":21728,"tag":"strategy2b","solution":"ia! ia!ia! ia!john bigboote r'lyehei!john bigbootenecronomiconyogsothothyuggothph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.yogsothothia! ia!john bigbooteei!ia! ia!ddia! ia!lei!pppddei!kkkyuggoth","problemId":6},{"seed":22079,"tag":"strategy2b","solution":"ia! ia!john bigbooteyogsothothei!john bigbootenecronomicon r'lyehia! ia!john bigbootenecronomiconnecronomiconph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.lyuggoth","problemId":6},{"seed":23220,"tag":"strategy2b","solution":"ia! ia!ia! ia!john bigbooteyogsothothnecronomiconei! r'lyehph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteia! ia!aei!ddia! ia!ia! ia!adddppaei!kkei!","problemId":6},{"seed":23256,"tag":"strategy2b","solution":"ia! ia!john bigbooteyogsothothph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconei!ia! ia!john bigbootenecronomiconei!aei!pia! ia!paaei!lei!aei!","problemId":6},{"seed":24334,"tag":"strategy2b","solution":"ia! ia!john bigbootenecronomicon r'lyehyogsothothei! r'lyehpdkakbbb r'lyehpdei!","problemId":6},{"seed":24513,"tag":"strategy2b","solution":"ia! ia!ia! ia!john bigboote r'lyehei!john bigbootenecronomiconyogsothothyuggothjohn bigbooteyogsothothjohn bigbooteia! ia!ia! ia!dbei!dei!aei!","problemId":6},{"seed":24524,"tag":"strategy2b","solution":"ia! ia!john bigbootenecronomicon r'lyehyogsothothei!john bigboote r'lyehpaayuggoth r'lyehpl","problemId":6},{"seed":24732,"tag":"strategy2b","solution":"ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbooteyogsothothnecronomiconyuggothei!ia! ia!necronomiconnecronomiconia! ia!alkbdbei!bbei!ppaalbbbbblaia! ia!l","problemId":6},{"seed":25267,"tag":"strategy2b","solution":"ia! ia!john bigbooteyogsothothph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconei!john bigbooteyuggothnecronomiconjohn bigbooteia! ia!ia! ia!ia! ia!ia! ia!dbei!bbbllkei!ddbdddei!lei!","problemId":6},{"seed":25460,"tag":"strategy2b","solution":"ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconyogsothothjohn bigbooteei!john bigbooteyuggothldpia! ia!ia! ia!aabkpdpkpapkaei!kpdpkkei!","problemId":6},{"seed":25499,"tag":"strategy2b","solution":"ia! ia!john bigboote r'lyehei!ia! ia!ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconnecronomiconia! ia!ia! ia!ia! ia! r'lyehia! ia!pkei!bblyuggoth","problemId":6},{"seed":25536,"tag":"strategy2b","solution":"ia! ia!ia! ia!john bigbooteyogsothothyuggothnecronomicon r'lyehei!necronomiconyogsothothyogsothothyuggothnecronomiconia! ia!ia! ia!kdlkbbei!pppdlaei!pppaabllaaei!aei!ppkl","problemId":6},{"seed":26670,"tag":"strategy2b","solution":"ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconei!ia! ia! r'lyehyuggothdbei!aei!pakkkei!l","problemId":6},{"seed":26708,"tag":"strategy2b","solution":"ia! ia!john bigbooteyogsothothnecronomiconei! r'lyehei!ei!bei!bbbei!lei!","problemId":6},{"seed":26906,"tag":"strategy2b","solution":"ia! ia!john bigbootenecronomiconph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.lei!ia! ia!bbb r'lyeh","problemId":6},{"seed":28599,"tag":"strategy2b","solution":"ia! ia!ia! ia!ia! ia!john bigbooteyogsothothnecronomicon r'lyehei!john bigbootejohn bigbooteyuggoth r'lyehyogsothothia! ia!ia! ia!ia! ia!ia! ia!llei!aei!ppdddbbbbbka r'lyehp","problemId":6},{"seed":2860,"tag":"strategy2b","solution":"ia! ia!john bigbootenecronomiconyogsothoth r'lyehei! r'lyehbei!kei!ei!","problemId":6},{"seed":29169,"tag":"strategy2b","solution":"ia! ia!john bigbootenecronomicon r'lyehei!ia! ia!john bigbooteia! ia!aei!lei!","problemId":6},{"seed":31026,"tag":"strategy2b","solution":"ia! ia!john bigbootenecronomicon r'lyehei!john bigbootenecronomiconyogsothothia! ia!ia! ia!ia! ia!ia! ia!john bigboote r'lyehpppaalabyuggothkkbdbbbdbkei!","problemId":6},{"seed":3703,"tag":"strategy2b","solution":"ia! ia!john bigbootenecronomicon r'lyehei!john bigbootenecronomiconia! ia!ia! ia!john bigbooteyogsothothyuggothjohn bigbootenecronomiconia! ia!ia! ia!ia! ia!necronomiconia! ia!kapadpkpdpakpkpdpkdddei!l","problemId":6},{"seed":5343,"tag":"strategy2b","solution":"ia! ia!john bigbootenecronomiconph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconei!necronomiconjohn bigbootenecronomiconia! ia!ia! ia! r'lyehia! ia!ia! ia!aei!aei!abbbei!ppaakei!lei!palei!","problemId":6},{"seed":629,"tag":"strategy2b","solution":"ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!necronomiconyogsothothjohn bigbooteyuggoth r'lyehei!ia! ia!john bigbootejohn bigbooteia! ia! r'lyehpaei!akkpkei!kei!l","problemId":6},{"seed":6839,"tag":"strategy2b","solution":"ia! ia!ia! ia!ia! ia!john bigbootenecronomicon r'lyehei!john bigbooteyogsothothph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconia! ia!aei!ei!kbbei!ppakei!kei!l","problemId":6},{"seed":7082,"tag":"strategy2b","solution":"ia! ia!john bigbooteyogsothothnecronomicon r'lyehei!john bigbooteyuggothyogsothothyogsothothyogsothothia! ia!ia! ia!kpakdbddppklblia! ia!aa","problemId":6},{"seed":7610,"tag":"strategy2b","solution":"ia! ia!john bigbooteyogsothothnecronomiconei!ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconjohn bigbooteyuggothnecronomiconbbei!ia! ia!pia! ia!aei!aei!apkei!kkbbdllaei!","problemId":6},{"seed":8123,"tag":"strategy2b","solution":"ia! ia!ia! ia!john bigbooteyogsothothnecronomiconei!necronomiconyuggoth r'lyeh r'lyehia! ia!ia! ia!ia! ia!aei!aei!apkei!akppaei!pkl","problemId":6},{"seed":8466,"tag":"strategy2b","solution":"ia! ia!john bigbootenecronomicon r'lyehyogsothothyuggothei!necronomiconnecronomiconyogsothothyogsothoth r'lyehei!dei!bei!bbbllei!bbbdbei!kei!","problemId":6},{"seed":8780,"tag":"strategy2b","solution":"ia! ia!john bigbooteyogsothothei!john bigbootenecronomicon r'lyehia! ia!john bigbooteyuggothnecronomiconia! ia!john bigbooteia! ia!ia! ia! r'lyehia! ia!ia! ia! r'lyehei!kei!kkbdbkkei!ppkei!","problemId":6},{"seed":8856,"tag":"strategy2b","solution":"ia! ia!ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.john bigbootenecronomiconei!john bigbooteyuggothia! ia!necronomiconbbei!ia! ia!abppppdlakbei!kkbkbdei!","problemId":6},{"seed":9536,"tag":"strategy2b","solution":"ia! ia!john bigboote r'lyehei!john bigbooteyuggothia! ia!john bigbootenecronomiconyogsothothjohn bigbooteyogsothothnecronomiconkyuggothia! ia!aei!kp r'lyeh","problemId":6},{"seed":9816,"tag":"strategy2b","solution":"ia! ia!john bigbootenecronomicon r'lyehyogsothothyuggothei!necronomiconjohn bigbootenecronomiconia! ia!ia! ia! r'lyehei!d r'lyeh","problemId":6}] diff --git a/submitted/7.json b/submitted/7.json index e65961c..6042a90 100644 --- a/submitted/7.json +++ b/submitted/7.json @@ -1 +1 @@ -[{"seed":0,"tag":"strategy2","solution":"bkadpkkbdbdakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkbdbdakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkkkkkbkakkkkkbkkkkkakkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkakkkkklkkkkklalaldpakkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkpkei!l","problemId":7},{"seed":16651,"tag":"strategy2","solution":"bbbkdei!kkkkkbddddbkdpkpdpkpdpkpdpkpdpkpdpkpdpkpdpkpdpkpdlkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkbkakkkkkbkkbdbkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkklkkkkkbkkkkkbkkkkkakkkkkpkldbkkkkldlalakpkkakkkkkbkkkkkakkkkkbkakkkkkei!kkkkkei!l","problemId":7},{"seed":18705,"tag":"strategy2","solution":"bkadpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkakkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkakkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkadbkkbkkbbdbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkakkei!kkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkakkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkakei!lbdakldpabkkakkbkkakkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkakkbkakkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkakkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkei!l","problemId":7},{"seed":22828,"tag":"strategy2","solution":"bbbkkkbkkdpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkppaalpaakpkbdpkppabpppppppppppppppppplkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkakkbkei!kkpkkpkkpkkpkkpkkpkklkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkapkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpklkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbdadpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpabdbdbkkbkkbbdbkkbdbbbdbkkbkkbkapkpllladabkkbei!kpkkakkbdbkakbbbkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkbkkakkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkkpkpkei!","problemId":7},{"seed":27669,"tag":"strategy2","solution":"bkdbdakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkadbkkkkkbkkkbdbdbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkakkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkakkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkbkkkkkei!kkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkkpkkkkadbdbkkkkkbkkkkkakkkkkaei!","problemId":7}] +[{"seed":0,"tag":"strategy2b","solution":"necronomiconph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconadbbbbdllei!kbldllllayogsothoth","problemId":7},{"seed":16651,"tag":"strategy2b","solution":"necronomiconjohn bigbooteyogsothothia! ia! r'lyehyuggothei!ablddbdbdlllyuggothaaakla r'lyeh r'lyehpl","problemId":7},{"seed":18705,"tag":"strategy2b","solution":"necronomiconyogsothothjohn bigbooteyuggoth r'lyehei!ia! ia!pdia! ia!akei!kkei!kbbdbkbdei!dei!","problemId":7},{"seed":22828,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.necronomiconia! ia!ia! ia!ei!kblei!kpkakdbkbdbnecronomiconllalayuggothei!kkei!l","problemId":7},{"seed":27669,"tag":"strategy2b","solution":"ph'nglui mglw'nafh cthulhu r'lyeh wgah'nagl fhtagn.ia! ia!ia! ia! r'lyehei!paakdpapkpia! ia!adpadalalayuggothdei!l","problemId":7}] diff --git a/submitted/8.json b/submitted/8.json index cb40a31..0c64169 100644 --- a/submitted/8.json +++ b/submitted/8.json @@ -1 +1 @@ -[{"seed":0,"tag":"strategy2","solution":"paalpaapaalpaapaalpaabbbbbbbbbbbbbbbbbbbbppaalpaapaalpaalbbbbbblbbbbblbbei!pabbbbei!ppppabbbbbei!ppppppppa","problemId":8},{"seed":10596,"tag":"strategy2","solution":"paalpaapaalpaapaalpaapbbkpppplbbbbbbbbei!ppppplbbbbbei!ppppabbbbbei!ppppppppa","problemId":8},{"seed":14104,"tag":"strategy2","solution":"paalpaapaalpaabbbbbbbpaalpaapabbbbbbbbbbbbbbbbbbbei!lbbbbblbbbblbbblbbllbbbbbllbbbbllbbbllbbllaplllbbbbblllbbei!pppabbbbbei!ppppppppa","problemId":8},{"seed":19012,"tag":"strategy2","solution":"paalpaapaalpaapaalpaabbbbbbbbbbbbbbbbbbei!lbbbbei!pppabbbbei!pppppppabbbbbbbbei!l","problemId":8},{"seed":20240,"tag":"strategy2","solution":"paalpaapaalpaapaalpaabbbbbbbbbbbbbbbbbbei!lbbbbei!pppabbbbei!pppppppabbbbbbbbei!l","problemId":8},{"seed":2629,"tag":"strategy2","solution":"paalpaapaalpaapaalpaapaalpaapbbbbbbbbbbbbbbbbbbbbppaalpaapaalpaalbbbbbblbbbbblbbbblbei!abbbbei!ppppabbbbbei!ppppppppa","problemId":8},{"seed":28581,"tag":"strategy2","solution":"paalpaapaalpaapaalpaapaalpaabbkpppplei!lbpppplei!ppppplei!","problemId":8},{"seed":4491,"tag":"strategy2","solution":"paalpaapaalpaapaalpaapaalpaapabbbbbbbbbei!abbei!pppabbbbei!pppppppabbbbbbbbei!l","problemId":8},{"seed":5696,"tag":"strategy2","solution":"paalpaapaalpaapaalpaapbbkpaalpaapaalpaalbbbbei!pppabbbbei!ppppabbbbbei!ppppppppa","problemId":8},{"seed":8000,"tag":"strategy2","solution":"paalpaapaalpaapaalpaapaalpaapbbbbbbbbbbbbbbbbbbbbppaalpaapaabbbbbei!pppplbbbbei!ppppabbbbbei!ppppppppa","problemId":8}] +[{"seed":0,"tag":"strategy2b","solution":"john bigbooteei!ia! ia!ei!ia! ia!abppia! ia!pabpppaaei!pppaappppalei!pppalbei!pppalbbei!pppalbbbei!pppalbbbbei!pppalbbbbbbei!aei!abbbei!","problemId":8},{"seed":10596,"tag":"strategy2b","solution":"necronomiconia! ia!ia! ia!ia! ia!ia! ia! r'lyehyuggothei!ia! ia!necronomiconia! ia!ia! ia!lia! ia!","problemId":8},{"seed":14104,"tag":"strategy2b","solution":"john bigbootebbei!bei!ia! ia!pia! ia!abppia! ia!pabpppaaei!pppaappppalei!pppalbei!pppalbei!ppalei!ppalbpppabppppppppppppppl","problemId":8},{"seed":19012,"tag":"strategy2b","solution":"john bigbooteei!ia! ia!ei!ia! ia!abppia! ia!paaablei!aei!l","problemId":8},{"seed":20240,"tag":"strategy2b","solution":"john bigbooteei!ia! ia!ei!ia! ia!abppia! ia!paaablei!aei!l","problemId":8},{"seed":2629,"tag":"strategy2b","solution":"necronomiconia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ei!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ei!aei!ei!abppia! ia!papaei!","problemId":8},{"seed":28581,"tag":"strategy2b","solution":"necronomiconia! ia!ia! ia!ia! ia!ia! ia!john bigbooteei!ia! ia!pia! ia!aaei!lei!aei!","problemId":8},{"seed":4491,"tag":"strategy2b","solution":"necronomiconia! ia!ia! ia!ia! ia!ia! ia!john bigbooteei!ia! ia!paaei!abei!aei!","problemId":8},{"seed":5696,"tag":"strategy2b","solution":"necronomiconia! ia!ia! ia!ia! ia!ia! ia! r'lyehyuggothei!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!aei!bei!bbei!bbbbei!aei!ppaei!aei!","problemId":8},{"seed":8000,"tag":"strategy2b","solution":"necronomiconia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ei!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ia! ia!ei!ayogsothoth r'lyehei!aei!aei!aei!bei!bbei!bbblei!aei!aei!l","problemId":8}] diff --git a/submitted/9.json b/submitted/9.json new file mode 100644 index 0000000..bd30a82 --- /dev/null +++ b/submitted/9.json @@ -0,0 +1 @@ +[{"seed":0,"tag":"strategy2b","solution":"necronomiconyuggoth r'lyehpapakbbei!paei!ppkl","problemId":9},{"seed":10998,"tag":"strategy2b","solution":"necronomiconia! ia!kbei!bbei!ppkkbbei!ppkl","problemId":9},{"seed":23855,"tag":"strategy2b","solution":"necronomiconia! ia!kbei!bbbb r'lyeh","problemId":9},{"seed":26637,"tag":"strategy2b","solution":"necronomiconyuggothia! ia!kbbll r'lyehppakbbei!ppkkbbei!ppkl","problemId":9},{"seed":4150,"tag":"strategy2b","solution":"necronomiconia! ia!kblbbdei!bei!bbbei!ppkkbbei!ppkl","problemId":9}] From e3601272a96291281163c3ecc395b9add7b30c05 Mon Sep 17 00:00:00 2001 From: Slash Date: Mon, 10 Aug 2015 09:55:32 +0200 Subject: [PATCH 10/11] hotfix --- src/Main.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 0042480..f2cffac 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -17,7 +17,7 @@ import Data.Maybe import StrategyManager import Strategy0 -import Datatypes.Game(Game,Command) +import Datatypes.Game(Game,Command,commandsToString) import VM import Opt import JSONDeser(readInput) @@ -76,7 +76,7 @@ main = do initTime <- secTime initialData <- createComputationsFromFiles files rng powerPhrase let (_, _,gameComputations) = unzip3 initialData commandResults <- iterateGame gameComputations (timeStruct maxTime initTime) maxMem - let stringResults = map (\(cmds,score,algoIdx) -> (cmdToString cmds,score,algoIdx)) commandResults + let stringResults = map (\(cmds,score,algoIdx) -> (commandsToString cmds,score,algoIdx)) commandResults let outJSONstructs = zipWith jsonBuilder initialData stringResults BS.putStrLn $ encode outJSONstructs writeLogFile logFile (zipWith logFileBuilder initialData stringResults) From 56f3f25099253cf4a1d4b9118160b2d1f52cf5c3 Mon Sep 17 00:00:00 2001 From: Andrea Bellandi Date: Mon, 10 Aug 2015 10:18:35 +0200 Subject: [PATCH 11/11] sistemate flag e pphrases --- icfp2015.cabal | 2 +- src/Datatypes/Game.hs | 2 +- src/Main.hs | 27 ++++++++++++--------------- src/Opt.hs | 6 +++--- src/Strategy0.hs | 2 +- src/StrategyManager.hs | 2 +- 6 files changed, 19 insertions(+), 22 deletions(-) diff --git a/icfp2015.cabal b/icfp2015.cabal index 175bb83..0b45249 100644 --- a/icfp2015.cabal +++ b/icfp2015.cabal @@ -60,7 +60,7 @@ executable icfp2015 other-extensions: OverloadedStrings, DeriveGeneric, DeriveDataTypeable -- Other library packages from which modules are imported. - build-depends: base >=4.6 && <4.9, hashable >=1.2 && <1.3, containers >=0.5 && <0.6, QuickCheck >=2.7 && <2.9, bytestring >=0.10 && <0.11, aeson >=0.8 && <0.9, pqueue >=1.3 && <1.4, clock, random, deepseq >= 1.3 && <1.4 + build-depends: base >=4.6 && <4.9, hashable >=1.2 && <1.3, containers >=0.5 && <0.6, QuickCheck >=2.7 && <2.9, bytestring >=0.10 && <0.11, aeson, pqueue >=1.3 && <1.4, clock, random, deepseq >= 1.3 && <1.4 -- Directories containing source files. hs-source-dirs: src diff --git a/src/Datatypes/Game.hs b/src/Datatypes/Game.hs index 2999a41..681ac63 100644 --- a/src/Datatypes/Game.hs +++ b/src/Datatypes/Game.hs @@ -1,4 +1,4 @@ -module Datatypes.Game (Game(..), Command(..), isCompleted, new, notifyCommand, powerCounterToScore, powerPhrasesAsCommands, commandsToString) where -- FIXME exports +module Datatypes.Game (Game(..), Command(..), isCompleted, new, notifyCommand, powerCounterToScore, powerPhrasesAsCommands, commandsToString,stringToCommands) where -- FIXME exports import Data.Hashable (hash) import qualified Data.List as List diff --git a/src/Main.hs b/src/Main.hs index f2cffac..a209ea1 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -13,15 +13,14 @@ import System.Random import System.Clock import GHC.Generics import Data.Aeson -import Data.Maybe import StrategyManager import Strategy0 -import Datatypes.Game(Game,Command,commandsToString) -import VM +import Datatypes.Game(Game,Command,commandsToString,stringToCommands) +--import VM import Opt import JSONDeser(readInput) -import PowerPhrases + strategyTag :: String strategyTag = "lilik0" @@ -52,7 +51,7 @@ type Id = Int type Seed = Int -strategies :: Game -> StdGen -> Maybe [Command] -> GameComputation +strategies :: Game -> StdGen -> [[Command]] -> GameComputation strategies g sgen cmd = [MkStrategyWrapper (initst g sgen cmd :: Strategy0)] -- = [MkStrategyWrapper (initst g sgen cmd :: NullStrategy1), @@ -70,10 +69,10 @@ main = do initTime <- secTime let files = optFile opt let maxTime = optTime opt let maxMem = optMem opt - let powerPhrase = optPowerPhrase opt + let powerPhrases = optPowerPhrase opt let logFile = optLog opt rng <- getStdGen - initialData <- createComputationsFromFiles files rng powerPhrase + initialData <- createComputationsFromFiles files rng powerPhrases let (_, _,gameComputations) = unzip3 initialData commandResults <- iterateGame gameComputations (timeStruct maxTime initTime) maxMem let stringResults = map (\(cmds,score,algoIdx) -> (commandsToString cmds,score,algoIdx)) commandResults @@ -89,19 +88,17 @@ main = do initTime <- secTime jsonBuilder (idx, seed, _) (strCmds, _, _) = (JSONSer idx seed strategyTag strCmds) logFileBuilder (idx, seed, _) (_ ,score , algoIdx) = (idx, seed, score, algoIdx) -createComputationsFromFiles :: [String] -> StdGen -> Maybe String -> IO [(Id,Seed,GameComputation)] -createComputationsFromFiles fileNames randomGen powerPhrase = do inputs <- readFiles fileNames - let igames = map readInput inputs - let cstruct = compstruct igames - return (gcstruct cstruct) +createComputationsFromFiles :: [String] -> StdGen -> [String] -> IO [(Id,Seed,GameComputation)] +createComputationsFromFiles fileNames randomGen powerPhrases = do inputs <- readFiles fileNames + let igames = map readInput inputs + let cstruct = compstruct igames + return (gcstruct cstruct) where compstruct ig = concat (map genf ig) genf (i,g) = zipWith (\x (y,z) -> (x,y,z)) (replicate (length g) i) g gcstruct cst = map (\(x,y,z) -> (x,y,j z)) cst where - j game = strategies game randomGen (powerCommands powerPhrase) - powerCommands Nothing = Nothing - powerCommands (Just a) = Just (mapMaybe charToCommand a) + j game = strategies game randomGen (map stringToCommands powerPhrases) readFiles :: [String] -> IO [BS.ByteString] readFiles [] = return [] diff --git a/src/Opt.hs b/src/Opt.hs index a17986c..f6ca4de 100644 --- a/src/Opt.hs +++ b/src/Opt.hs @@ -14,7 +14,7 @@ data Flag = File String data Options = Options { optFile :: [String], optTime :: Maybe Int, optMem :: Maybe Int, - optPowerPhrase :: Maybe String, + optPowerPhrase :: [String], optSeedNumber :: Int, optCores :: Int, optLog :: Bool @@ -24,7 +24,7 @@ data Options = Options { optFile :: [String], startOptions = Options { optFile = [], optTime = Nothing, optMem = Nothing, - optPowerPhrase = Nothing, + optPowerPhrase = [], optSeedNumber = 0, optCores = 1, optLog = True @@ -48,7 +48,7 @@ options = [ Option "f" ["filename"] "Memory Limit in MB" , Option "p" ["phrasepower"] (ReqArg - (\arg opt -> return opt { optPowerPhrase = Just arg }) + (\arg opt -> return opt { optPowerPhrase = (arg:(optPowerPhrase opt)) }) "POWERPHRASE") "Power Phrase" , Option "n" ["seednumber"] diff --git a/src/Strategy0.hs b/src/Strategy0.hs index e52dde4..a81c02d 100644 --- a/src/Strategy0.hs +++ b/src/Strategy0.hs @@ -24,7 +24,7 @@ instance Strategy Strategy0 where advance = strategy0advance getbest = strategy0getbest -strategy0initst :: Game -> StdGen -> Maybe [Command] -> Strategy0 +strategy0initst :: Game -> StdGen -> [[Command]] -> Strategy0 strategy0initst game _ _ = (Strategy0 (firstQueue, firstList)) where firstQueue = PQ.singleton (fullScore game, -(length $ Game.units game), snd . Unit.pivot . head . Game.units $ game) game firstList = [] diff --git a/src/StrategyManager.hs b/src/StrategyManager.hs index cb8b3bb..e0703de 100644 --- a/src/StrategyManager.hs +++ b/src/StrategyManager.hs @@ -23,7 +23,7 @@ initWrapper :: Strategy a => a -> StrategyWrapper initWrapper = MkStrategyWrapper class Strategy a where - initst :: Game -> StdGen -> Maybe [Command] -> a + initst :: Game -> StdGen -> [[Command]] -> a advance :: a -> Either a ([Command], Int) getbest :: a -> ([Command], Int)