You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.

35 lines
1.1 KiB

{-# 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
import VM (Command, cmdToString)
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 "lilik0" y) seeds commandStrings
where
commandStrings = map cmdToString commandLists