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.

50 lines
1.6 KiB

{-# LANGUAGE DeriveGeneric #-}
module Main where
import GHC.Generics
import Data.Aeson
import Data.Aeson.Types
import System.Environment
import qualified Data.ByteString.Lazy as BS
import System.IO
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, Generic)
instance FromJSON JSONSer
instance ToJSON JSONSer
main :: IO ()
main = do args <- getArgs
opt <- parseArgs args
file <- return ((optFile opt) !! 0)
str <- BS.readFile file
(id, gmseed) <- return (readInput str)
commandspoints <- return (map (\(seed,game) -> strat0 game) gmseed)
(commands,points) <- return $ unzip commandspoints
seeds <- return ((map (\(seed, _) -> seed)) gmseed)
putStrLn $ show $ encode $ (packAll id seeds commands)
writeFile ("scores") (scoredata id (fst $ unzip gmseed) points)
packAll :: Int -> [Int] -> [[Command]] -> [JSONSer]
packAll id seeds commandLists = zipWith (\x y -> JSONSer id x "lilik0" y) seeds commandStrings
where
commandStrings = map cmdToString commandLists
scoredata :: Int -> [Int] -> [Int] -> String
scoredata id seeds points = pretty
where
pretty = foldl (\x (a,b,c) -> (show a) ++ " " ++ (show b) ++ (show c) ++ "\n" ++ x) "" zipdata
zipdata = zip3 ids seeds points
ids = replicate (length seeds) id