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) +