Browse Source

prima prova con Strategy0

adaptedStrategy0
Andrea Bellandi 9 years ago
parent
commit
1d55ddd9fe
2 changed files with 66 additions and 4 deletions
  1. +32
    -4
      vm/JSONDeser.hs
  2. +34
    -0
      vm/Main0.hs

+ 32
- 4
vm/JSONDeser.hs View File

@ -1,10 +1,13 @@
{-# LANGUAGE OverloadedStrings, DeriveGeneric #-}
module JSONDeser where
module JSONDeser(readInput) where
import qualified Data.Set as Set
import Data.Maybe
import Data.ByteString.Lazy
import qualified Data.ByteString.Lazy as BS
import Data.Aeson
import GHC.Generics
import qualified Datatypes as DT
import LCG
data Cell = Cell { x :: Int, y :: Int}
@ -33,7 +36,10 @@ instance ToJSON Unit
instance FromJSON Input
instance ToJSON Input
readInputInternal :: ByteString -> Input
readInput :: BS.ByteString -> (Int,[(Int,DT.Game)])
readInput str = newGame (readInputInternal str)
readInputInternal :: BS.ByteString -> Input
readInputInternal str = if isJust result
then fromJust result
else error "Error during JSON parsing"
@ -41,4 +47,26 @@ readInputInternal str = if isJust result
result = (decode str :: Maybe Input)
newGame :: Input -> (Int,[(Int,DT.Game)])
newGame input = (JSONDeser.id input, zip (sourceSeeds input) (map gameFromSeed (sourceSeeds input)))
where
gameFromSeed seed = DT.Game board (seedUnits seed input) (Set.empty :: Set.Set Int) 0 0
board = DT.Board w h filledel
w = width input
h = height input
filledel = Set.fromList (map cellConvVM (filled input))
seedUnits :: Int -> Input -> [DT.Unit]
seedUnits s input = map (\x -> uinput !! x ) unit_index
where
unit_index = lcg s (length (units input)) (sourceLength input)
uinput = map unitConvVM (units input)
cellConvVM :: Cell -> DT.Cell
cellConvVM (Cell x y) = (x,y)
unitConvVM :: Unit -> DT.Unit
unitConvVM unit = DT.Unit setcell (cellConvVM (pivot unit))
where
setcell = Set.fromList (map cellConvVM (members unit))

+ 34
- 0
vm/Main0.hs View File

@ -0,0 +1,34 @@
{-# LANGUAGE DeriveDataTypeable #-}
module Main where
import System.Environment
import qualified Data.ByteString.Lazy as BS
import System.IO
import Text.JSON.Generic
import Datatypes
import Opt
import JSONDeser
import Strategy0
data JSONSer = JSONSer { problemId :: Int,
seed :: Int,
tag :: String,
solution :: String
} deriving (Show, Data, Typeable)
main :: IO ()
main = do args <- getArgs
opt <- parseArgs args
file <- return ((optFile opt) !! 0)
str <- BS.readFile file
(id, gmseed) <- return (readInput str)
commands <- return (map (\(seed,game) -> strat0 game) gmseed)
seeds <- return ((map (\(seed, _) -> seed)) gmseed)
putStrLn . encodeJSON $ (packAll id seeds commands)
packAll :: Int -> [Int] -> [[Command]] -> [JSONSer]
packAll id seeds commandLists = zipWith (\x y -> JSONSer id x "cazziammolla" y) seeds commandStrings
where
commandStrings = map cmdToString commandLists

Loading…
Cancel
Save